Skip to content

Commit 3b02302

Browse files
committed
Add support for loading multiple components into one repl session
There are several parts to this patch which are logically distinct but work together to support the overal goal of starting a GHCi session with multiple packages loaded at once. 1. When a user writes "cabal repl <target>" then if the user is using a compiler > ghc-9.4.* then we will attempt to start a multi-session which loads the selected targets into one multi-package session of GHC. 1a. The closure property states that in order to load components `p` and `q` into the same session that if `p` depends on `z` and `z` depends on `q` then `z` must also be loaded into the session. 1b. Only inplace packages are able to be loaded into a multi session (if a component `z` exists then it is already made into an inplace package by cabal). Therefore cabal has already engineered that there is source code locally available for all packages which we will want to load into a session. 2. It is necessary to modify `./Setup configure` to allow users to configure a package *without* having previously built the dependency. Instead, we promise to the configure phase that we will have built it by the time we build the package. This allows us to configure all the packages we intend to load into the repl without building any dependenices which we will load in the same session, because the promise is satisifed due to loading the package and it's dependency into one multi-session which ensures the dependency is built before it is needed. A user of ./Setup configure specifies a promised dependency by prepending a "+" to a normal dependency specification. For example: ``` '--dependency=+cabal-install-solver=cabal-install-solver-3.9.0.0-inplace' ``` 2a. The `./Setup repl` command is modified to allow a user to defer starting the repl and instead instruct the command to write the necessary build flags to a file. The option is called `--repl-multi-file <FILEPATH>`. `cabal-install` then invokes this command for each component which will populate the session and starts a multi-session with all the arguments together. 3. The solver is unmodified, the solver is given the repl targets and creates a build plan as before. After the solver is completed then in `setRootTargets` and `pruneInstallPlan` we modify the install plan to enforce the closure property and mark which dependencies need to be promised. * Mark the current components as `BuildInPlaceOnly InMemory`, which indicates to the compiler that it is to be built in a GHC multi-session. * Augment the component repl targets to indicate that components required by the closure property (in addition to normal targets) will be loaded into the repl. * Modify the dependency edges in `compLibDependencies` to indicate which dependencies are the promised ones (which is precisely components which are `BuildInPlaceOnly InMemory` build styles). This is the field which is eventually used to populate the `--dependency` argument to `./Setup configure`. Pass this-unit-id for executable components as well as libraries When starting multi-repl sessions we can have multiple executables so it's important to distinguish between the different units. undo wip wip - pass all unit-id error messages C files and Setup.hs filtering pruning Missing file Keep temp files in cabal multirepl Undo changes in cabal.project, make tests compile Use cabal.project.local for allow-newer stuff.
1 parent a5ddb14 commit 3b02302

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

49 files changed

+906
-329
lines changed

Cabal-syntax/src/Distribution/Types/ExposedModule.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE DeriveDataTypeable #-}
22
{-# LANGUAGE DeriveGeneric #-}
3+
{-# LANGUAGE ScopedTypeVariables #-}
34
module Distribution.Types.ExposedModule where
45

56
import Distribution.Compat.Prelude

Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ tests = testGroup "Distribution.Utils.Structured"
2929
, testCase "GenericPackageDescription" $
3030
md5Check (Proxy :: Proxy GenericPackageDescription) 0xa3e9433662ecf0c7a3c26f6d75a53ba1
3131
, testCase "LocalBuildInfo" $
32-
md5Check (Proxy :: Proxy LocalBuildInfo) 0x91ffcd61bbd83525e8edba877435a031
32+
md5Check (Proxy :: Proxy LocalBuildInfo) 0x8b9d831610716b11342d0a6242b144b3
3333
#endif
3434
]
3535

Cabal/src/Distribution/Backpack/Configure.hs

Lines changed: 22 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ import Distribution.Verbosity
4646
import qualified Distribution.Compat.Graph as Graph
4747
import Distribution.Compat.Graph (Graph, IsNode(..))
4848
import Distribution.Utils.LogProgress
49+
import Distribution.Backpack.ModuleShape
4950

5051
import Data.Either
5152
( lefts )
@@ -66,15 +67,15 @@ configureComponentLocalBuildInfos
6667
-> Flag String -- configIPID
6768
-> Flag ComponentId -- configCID
6869
-> PackageDescription
69-
-> [PreExistingComponent]
70+
-> ([PreExistingComponent], [FakePreExistingComponent])
7071
-> FlagAssignment -- configConfigurationsFlags
7172
-> [(ModuleName, Module)] -- configInstantiateWith
7273
-> InstalledPackageIndex
7374
-> Compiler
7475
-> LogProgress ([ComponentLocalBuildInfo], InstalledPackageIndex)
7576
configureComponentLocalBuildInfos
7677
verbosity use_external_internal_deps enabled deterministic ipid_flag cid_flag pkg_descr
77-
prePkgDeps flagAssignment instantiate_with installedPackageSet comp = do
78+
(prePkgDeps, promisedPkgDeps) flagAssignment instantiate_with installedPackageSet comp = do
7879
-- NB: In single component mode, this returns a *single* component.
7980
-- In this graph, the graph is NOT closed.
8081
graph0 <- case mkComponentsGraph enabled pkg_descr of
@@ -92,6 +93,10 @@ configureComponentLocalBuildInfos
9293
ann_cname = pc_compname pkg
9394
}))
9495
| pkg <- prePkgDeps]
96+
`Map.union`
97+
Map.fromListWith Map.union
98+
[ (pkg, Map.singleton (ann_cname aid) aid)
99+
| FakePreExistingComponent pkg aid <- promisedPkgDeps]
95100
graph1 <- toConfiguredComponents use_external_internal_deps
96101
flagAssignment
97102
deterministic ipid_flag cid_flag pkg_descr
@@ -102,13 +107,17 @@ configureComponentLocalBuildInfos
102107
let shape_pkg_map = Map.fromList
103108
[ (pc_cid pkg, (pc_open_uid pkg, pc_shape pkg))
104109
| pkg <- prePkgDeps]
110+
`Map.union`
111+
Map.fromList
112+
[ (ann_id aid, (DefiniteUnitId (unsafeMkDefUnitId $ mkUnitId (unComponentId (ann_id aid) )), emptyModuleShape))
113+
| FakePreExistingComponent _ aid <- promisedPkgDeps]
105114
uid_lookup def_uid
106115
| Just pkg <- PackageIndex.lookupUnitId installedPackageSet uid
107116
= FullUnitId (Installed.installedComponentId pkg)
108117
(Map.fromList (Installed.instantiatedWith pkg))
109118
| otherwise = error ("uid_lookup: " ++ prettyShow uid)
110119
where uid = unDefUnitId def_uid
111-
graph2 <- toLinkedComponents verbosity uid_lookup
120+
graph2 <- toLinkedComponents verbosity (not (null promisedPkgDeps)) uid_lookup
112121
(package pkg_descr) shape_pkg_map graph1
113122

114123
infoProgress $
@@ -129,7 +138,7 @@ configureComponentLocalBuildInfos
129138
infoProgress $ hang (text "Ready component graph:") 4
130139
(vcat (map dispReadyComponent graph4))
131140

132-
toComponentLocalBuildInfos comp installedPackageSet pkg_descr prePkgDeps graph4
141+
toComponentLocalBuildInfos comp installedPackageSet promisedPkgDeps pkg_descr prePkgDeps graph4
133142

134143
------------------------------------------------------------------------------
135144
-- ComponentLocalBuildInfo
@@ -138,13 +147,14 @@ configureComponentLocalBuildInfos
138147
toComponentLocalBuildInfos
139148
:: Compiler
140149
-> InstalledPackageIndex -- FULL set
150+
-> [FakePreExistingComponent]
141151
-> PackageDescription
142152
-> [PreExistingComponent] -- external package deps
143153
-> [ReadyComponent]
144154
-> LogProgress ([ComponentLocalBuildInfo],
145155
InstalledPackageIndex) -- only relevant packages
146156
toComponentLocalBuildInfos
147-
comp installedPackageSet pkg_descr externalPkgDeps graph = do
157+
comp installedPackageSet promisedPkgDeps pkg_descr externalPkgDeps graph = do
148158
-- Check and make sure that every instantiated component exists.
149159
-- We have to do this now, because prior to linking/instantiating
150160
-- we don't actually know what the full set of 'UnitId's we need
@@ -178,9 +188,15 @@ toComponentLocalBuildInfos
178188
--
179189
packageDependsIndex = PackageIndex.fromList (lefts local_graph)
180190
fullIndex = Graph.fromDistinctList local_graph
191+
181192
case Graph.broken fullIndex of
182193
[] -> return ()
183-
broken ->
194+
-- If there are promised dependencies, we don't know what the dependencies
195+
-- of these are and that can easily lead to a broken graph. So assume that
196+
-- any promised package is not broken (ie all its dependencies, transitively,
197+
-- will be there). That's a promise.
198+
broken | not (null promisedPkgDeps) -> return ()
199+
| otherwise ->
184200
-- TODO: ppr this
185201
dieProgress . text $
186202
"The following packages are broken because other"

Cabal/src/Distribution/Backpack/ConfiguredComponent.hs

Lines changed: 14 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ import qualified Data.Map as Map
4949
import Distribution.Pretty
5050
import Text.PrettyPrint (Doc, hang, text, vcat, hsep, quotes, ($$))
5151
import qualified Text.PrettyPrint as PP
52+
import Distribution.Compat.Stack
5253

5354
-- | A configured component, we know exactly what its 'ComponentId' is,
5455
-- and the 'ComponentId's of the things it depends on.
@@ -177,22 +178,23 @@ toConfiguredComponent pkg_descr this_cid lib_dep_map exe_dep_map component = do
177178
if newPackageDepsBehaviour pkg_descr
178179
then fmap concat $ forM (targetBuildDepends bi) $
179180
\(Dependency name _ sublibs) -> do
180-
pkg <- case Map.lookup name lib_dep_map of
181+
case Map.lookup name lib_dep_map of
181182
Nothing ->
182183
dieProgress $
183184
text "Dependency on unbuildable" <+>
184185
text "package" <+> pretty name
185-
Just p -> return p
186-
-- Return all library components
187-
forM (NonEmptySet.toList sublibs) $ \lib ->
188-
let comp = CLibName lib in
189-
case Map.lookup comp pkg of
190-
Nothing ->
191-
dieProgress $
192-
text "Dependency on unbuildable" <+>
193-
text (showLibraryName lib) <+>
194-
text "from" <+> pretty name
195-
Just v -> return v
186+
$$ text (prettyCallStack callStack)
187+
Just pkg -> do
188+
-- Return all library components
189+
forM (NonEmptySet.toList sublibs) $ \lib ->
190+
let comp = CLibName lib in
191+
case Map.lookup comp pkg of
192+
Nothing ->
193+
dieProgress $
194+
text "Dependency on unbuildable" <+>
195+
text (showLibraryName lib) <+>
196+
text "from" <+> pretty name
197+
Just v -> return v
196198
else return old_style_lib_deps
197199
mkConfiguredComponent
198200
pkg_descr this_cid

Cabal/src/Distribution/Backpack/LinkedComponent.hs

Lines changed: 27 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -114,12 +114,13 @@ instance Package LinkedComponent where
114114

115115
toLinkedComponent
116116
:: Verbosity
117+
-> Bool
117118
-> FullDb
118119
-> PackageId
119120
-> LinkedComponentMap
120121
-> ConfiguredComponent
121122
-> LogProgress LinkedComponent
122-
toLinkedComponent verbosity db this_pid pkg_map ConfiguredComponent {
123+
toLinkedComponent verbosity any_promised db this_pid pkg_map ConfiguredComponent {
123124
cc_ann_id = aid@AnnotatedId { ann_id = this_cid },
124125
cc_component = component,
125126
cc_exe_deps = exe_deps,
@@ -276,9 +277,14 @@ toLinkedComponent verbosity db this_pid pkg_map ConfiguredComponent {
276277
case filter (\x' -> unWithSource x /= unWithSource x') xs of
277278
[] -> return ()
278279
_ -> Left $ ambiguousReexportMsg reex x xs
279-
return (to, unWithSource x)
280+
return (to, Just (unWithSource x))
280281
_ ->
281-
Left (brokenReexportMsg reex)
282+
-- Can't resolve it right now.. carry on with the assumption it will be resolved
283+
-- dynamically later by an in-memory package which hasn't been installed yet.
284+
if any_promised
285+
then return (to, Nothing)
286+
-- But if nothing is promised, eagerly report an error, as we already know everything.
287+
else Left (brokenReexportMsg reex)
282288

283289
-- TODO: maybe check this earlier; it's syntactically obvious.
284290
let build_reexports m (k, v)
@@ -289,8 +295,20 @@ toLinkedComponent verbosity db this_pid pkg_map ConfiguredComponent {
289295
provs <- foldM build_reexports Map.empty $
290296
-- TODO: doublecheck we have checked for
291297
-- src_provs duplicates already!
292-
[ (mod_name, OpenModule this_uid mod_name) | mod_name <- src_provs ] ++
293-
reexports_list
298+
-- These are normal module exports.
299+
[ (mod_name, (OpenModule this_uid mod_name)) | mod_name <- src_provs ]
300+
++
301+
-- These are reexports, which we managed to resolve to something in an external package.
302+
[(mn_new, om) | (mn_new, Just om) <- reexports_list ]
303+
++
304+
-- These ones.. we didn't resolve but also we might not have to resolve them because they could come from a promised unit, which we don't know
305+
-- anything about yet. GHC will resolve these itself when it is dealing with the multi-session. These ones will not be built, registered and put
306+
-- into a package database, we only need them to make it as far as generating GHC options where the info will be used to pass the reexported-module option
307+
-- to GHC.
308+
309+
-- We also know that in the case there are promised units that we will not be doing anything to do with backpack like unification etc..
310+
[ (mod_name, (OpenModule (DefiniteUnitId (unsafeMkDefUnitId (mkUnitId "fake"))) mod_name)) | (mod_name, Nothing) <- reexports_list ]
311+
-- [(mn_new, OpenModule mn_new) | (mn_new, Nothing) <- reexports_list ]
294312

295313
let final_linked_shape = ModuleShape provs (Map.keysSet (modScopeRequires linked_shape))
296314

@@ -337,20 +355,22 @@ toLinkedComponent verbosity db this_pid pkg_map ConfiguredComponent {
337355
-- every ComponentId gets converted into a UnitId by way of SimpleUnitId.
338356
toLinkedComponents
339357
:: Verbosity
358+
-> Bool -- ^ Whether there are any "promised" package dependencies which we won't
359+
-- find already installed.
340360
-> FullDb
341361
-> PackageId
342362
-> LinkedComponentMap
343363
-> [ConfiguredComponent]
344364
-> LogProgress [LinkedComponent]
345-
toLinkedComponents verbosity db this_pid lc_map0 comps
365+
toLinkedComponents verbosity any_promised db this_pid lc_map0 comps
346366
= fmap snd (mapAccumM go lc_map0 comps)
347367
where
348368
go :: Map ComponentId (OpenUnitId, ModuleShape)
349369
-> ConfiguredComponent
350370
-> LogProgress (Map ComponentId (OpenUnitId, ModuleShape), LinkedComponent)
351371
go lc_map cc = do
352372
lc <- addProgressCtx (text "In the stanza" <+> text (componentNameStanza (cc_name cc))) $
353-
toLinkedComponent verbosity db this_pid lc_map cc
373+
toLinkedComponent verbosity any_promised db this_pid lc_map cc
354374
return (extendLinkedComponentMap lc lc_map, lc)
355375

356376
type LinkedComponentMap = Map ComponentId (OpenUnitId, ModuleShape)

Cabal/src/Distribution/Backpack/PreExistingComponent.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
-- | See <https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst>
22
module Distribution.Backpack.PreExistingComponent (
33
PreExistingComponent(..),
4+
FakePreExistingComponent(..),
45
ipiToPreExistingComponent,
56
) where
67

@@ -20,6 +21,9 @@ import Distribution.Package
2021
import qualified Data.Map as Map
2122
import qualified Distribution.InstalledPackageInfo as Installed
2223
import Distribution.InstalledPackageInfo (InstalledPackageInfo)
24+
import Distribution.Types.AnnotatedId
25+
26+
data FakePreExistingComponent = FakePreExistingComponent PackageName (AnnotatedId ComponentId)
2327

2428
-- | Stripped down version of 'LinkedComponent' for things
2529
-- we don't need to know how to build.
@@ -56,6 +60,7 @@ ipiToPreExistingComponent ipi =
5660
pc_shape = shapeInstalledPackage ipi
5761
}
5862

63+
5964
instance HasMungedPackageId PreExistingComponent where
6065
mungedId = pc_munged_id
6166

Cabal/src/Distribution/Compat/ResponseFile.hs

Lines changed: 16 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
-- Compatibility layer for GHC.ResponseFile
44
-- Implementation from base 4.12.0 is used.
55
-- http://hackage.haskell.org/package/base-4.12.0.0/src/LICENSE
6-
module Distribution.Compat.ResponseFile (expandResponse) where
6+
module Distribution.Compat.ResponseFile (expandResponse, escapeArgs) where
77

88
import Distribution.Compat.Prelude
99
import Prelude ()
@@ -13,7 +13,7 @@ import System.IO (hPutStrLn, stderr)
1313
import System.IO.Error
1414

1515
#if MIN_VERSION_base(4,12,0)
16-
import GHC.ResponseFile (unescapeArgs)
16+
import GHC.ResponseFile (unescapeArgs, escapeArgs)
1717
#else
1818

1919
unescapeArgs :: String -> [String]
@@ -47,6 +47,20 @@ unescape args = reverse . map reverse $ go args NoneQ False [] []
4747
| '"' == c = go cs DblQ False a as
4848
| otherwise = go cs NoneQ False (c:a) as
4949

50+
escapeArgs :: [String] -> String
51+
escapeArgs = unlines . map escapeArg
52+
53+
escapeArg :: String -> String
54+
escapeArg = reverse . foldl' escape []
55+
56+
escape :: String -> Char -> String
57+
escape cs c
58+
| isSpace c
59+
|| '\\' == c
60+
|| '\'' == c
61+
|| '"' == c = c:'\\':cs -- n.b., our caller must reverse the result
62+
| otherwise = c:cs
63+
5064
#endif
5165

5266
expandResponse :: [String] -> IO [String]

0 commit comments

Comments
 (0)