@@ -15,12 +15,12 @@ module Stack.Build.ConstructPlan
15
15
( constructPlan
16
16
) where
17
17
18
- import Control.Arrow ((&&&) )
19
18
import Control.Exception.Lifted
20
19
import Control.Monad
21
20
import Control.Monad.IO.Class
22
21
import Control.Monad.Logger
23
22
import Control.Monad.RWS.Strict
23
+ import Control.Monad.State.Strict (execState )
24
24
import Control.Monad.Trans.Resource
25
25
import Data.Either
26
26
import Data.Function
@@ -156,7 +156,6 @@ constructPlan :: forall env m. (StackM env m, HasEnvConfig env)
156
156
-> m Plan
157
157
constructPlan mbp0 baseConfigOpts0 locals extraToBuild0 localDumpPkgs loadPackage0 sourceMap installedMap = do
158
158
$ logDebug " Constructing the build plan"
159
- let locallyRegistered = Map. fromList $ map (dpGhcPkgId &&& dpPackageIdent) localDumpPkgs
160
159
getVersions0 <- getPackageVersionsIO
161
160
162
161
econfig <- view envConfigL
@@ -186,7 +185,7 @@ constructPlan mbp0 baseConfigOpts0 locals extraToBuild0 localDumpPkgs loadPackag
186
185
return $ takeSubset Plan
187
186
{ planTasks = tasks
188
187
, planFinals = M. fromList finals
189
- , planUnregisterLocal = mkUnregisterLocal tasks dirtyReason locallyRegistered sourceMap
188
+ , planUnregisterLocal = mkUnregisterLocal tasks dirtyReason localDumpPkgs sourceMap
190
189
, planInstallExes =
191
190
if boptsInstallExes $ bcoBuildOpts baseConfigOpts0
192
191
then installExes
@@ -219,29 +218,78 @@ constructPlan mbp0 baseConfigOpts0 locals extraToBuild0 localDumpPkgs loadPackag
219
218
-- or local packages.
220
219
toolMap = getToolMap mbp0
221
220
221
+ -- | State to be maintained during the calculation of local packages
222
+ -- to unregister.
223
+ data UnregisterState = UnregisterState
224
+ { usToUnregister :: ! (Map GhcPkgId (PackageIdentifier , Text ))
225
+ , usKeep :: ! [DumpPackage () () () ]
226
+ , usAnyAdded :: ! Bool
227
+ }
228
+
222
229
-- | Determine which packages to unregister based on the given tasks and
223
230
-- already registered local packages
224
231
mkUnregisterLocal :: Map PackageName Task
232
+ -- ^ Tasks
225
233
-> Map PackageName Text
226
- -> Map GhcPkgId PackageIdentifier
234
+ -- ^ Reasons why packages are dirty and must be rebuilt
235
+ -> [DumpPackage () () () ]
236
+ -- ^ Local package database dump
227
237
-> SourceMap
228
- -> Map GhcPkgId (PackageIdentifier , Maybe Text )
229
- mkUnregisterLocal tasks dirtyReason locallyRegistered sourceMap =
230
- Map. unions $ map toUnregisterMap $ Map. toList locallyRegistered
238
+ -> Map GhcPkgId (PackageIdentifier , Text )
239
+ mkUnregisterLocal tasks dirtyReason localDumpPkgs sourceMap =
240
+ -- We'll take multiple passes through the local packages. This
241
+ -- will allow us to detect that a package should be unregistered,
242
+ -- as well as all packages directly or transitively depending on
243
+ -- it.
244
+ loop Map. empty localDumpPkgs
231
245
where
232
- toUnregisterMap (gid, ident) =
233
- case M. lookup name tasks of
234
- Nothing ->
235
- case M. lookup name sourceMap of
236
- Just (PSUpstream _ Snap _ _ _) -> Map. singleton gid
237
- ( ident
238
- , Just " Switching to snapshot installed package"
239
- )
240
- _ -> Map. empty
241
- Just _ -> Map. singleton gid
242
- ( ident
243
- , Map. lookup name dirtyReason
244
- )
246
+ loop toUnregister keep
247
+ -- If any new packages were added to the unregister Map, we
248
+ -- need to loop through the remaining packages again to detect
249
+ -- if a transitive dependency is being unregistered.
250
+ | usAnyAdded us = loop (usToUnregister us) (usKeep us)
251
+ -- Nothing added, so we've already caught them all. Return the
252
+ -- Map we've already calculated.
253
+ | otherwise = usToUnregister us
254
+ where
255
+ -- Run the unregister checking function on all packages we
256
+ -- currently think we'll be keeping.
257
+ us = execState (mapM_ go keep) UnregisterState
258
+ { usToUnregister = toUnregister
259
+ , usKeep = []
260
+ , usAnyAdded = False
261
+ }
262
+
263
+ go dp = do
264
+ us <- get
265
+ case go' (usToUnregister us) ident deps of
266
+ -- Not unregistering, add it to the keep list
267
+ Nothing -> put us { usKeep = dp : usKeep us }
268
+ -- Unregistering, add it to the unregister Map and
269
+ -- indicate that a package was in fact added to the
270
+ -- unregister Map so we loop again.
271
+ Just reason -> put us
272
+ { usToUnregister = Map. insert gid (ident, reason) (usToUnregister us)
273
+ , usAnyAdded = True
274
+ }
275
+ where
276
+ gid = dpGhcPkgId dp
277
+ ident = dpPackageIdent dp
278
+ deps = dpDepends dp
279
+
280
+ go' toUnregister ident deps
281
+ -- If we're planning on running a task on it, then it must be
282
+ -- unregistered
283
+ | Just _ <- Map. lookup name tasks
284
+ = Just $ fromMaybe undefined $ Map. lookup name dirtyReason
285
+ -- Check if we're no longer using the local version
286
+ | Just (PSUpstream _ Snap _ _ _) <- Map. lookup name sourceMap
287
+ = Just " Switching to snapshot installed package"
288
+ -- Check if a dependency is going to be unregistered
289
+ | (dep, _): _ <- mapMaybe (`Map.lookup` toUnregister) deps
290
+ = Just $ " Dependency being unregistered: " <> packageIdentifierText dep
291
+ -- None of the above, keep it!
292
+ | otherwise = Nothing
245
293
where
246
294
name = packageIdentifierName ident
247
295
0 commit comments