@@ -31,7 +31,7 @@ import Distribution.Client.ProjectConfig
31
31
( ProjectConfig (.. ), withProjectOrGlobalConfigIgn
32
32
, projectConfigConfigFile )
33
33
import Distribution.Client.ProjectOrchestration
34
- import Distribution.Client.ProjectPlanning
34
+ import Distribution.Client.ProjectPlanning
35
35
( ElaboratedSharedConfig (.. ), ElaboratedInstallPlan )
36
36
import Distribution.Client.ProjectPlanning.Types
37
37
( elabOrderExeDependencies )
@@ -109,7 +109,7 @@ import System.FilePath
109
109
110
110
type ReplFlags = [String ]
111
111
112
- data EnvFlags = EnvFlags
112
+ data EnvFlags = EnvFlags
113
113
{ envPackages :: [Dependency ]
114
114
, envIncludeTransitive :: Flag Bool
115
115
, envIgnoreProject :: Flag Bool
@@ -125,9 +125,9 @@ defaultEnvFlags = EnvFlags
125
125
envOptions :: ShowOrParseArgs -> [OptionField EnvFlags ]
126
126
envOptions _ =
127
127
[ option [' b' ] [" build-depends" ]
128
- " Include an additional package in the environment presented to GHCi."
128
+ " Include additional packages in the environment presented to GHCi."
129
129
envPackages (\ p flags -> flags { envPackages = p ++ envPackages flags })
130
- (reqArg " DEPENDENCY " dependencyReadE (fmap prettyShow :: [Dependency ] -> [String ]))
130
+ (reqArg " DEPENDENCIES " dependencyReadE (fmap prettyShow :: [Dependency ] -> [String ]))
131
131
, option [] [" no-transitive-deps" ]
132
132
" Don't automatically include transitive dependencies of requested packages."
133
133
envIncludeTransitive (\ p flags -> flags { envIncludeTransitive = p })
@@ -234,7 +234,7 @@ replAction ( configFlags, configExFlags, installFlags
234
234
ignoreProject = fromFlagOrDefault False (envIgnoreProject envFlags)
235
235
with = withProject cliConfig verbosity targetStrings
236
236
without config = withoutProject (config <> cliConfig) verbosity targetStrings
237
-
237
+
238
238
(baseCtx, targetSelectors, finalizer, replType) <-
239
239
withProjectOrGlobalConfigIgn ignoreProject verbosity globalConfigFlag with without
240
240
@@ -252,65 +252,65 @@ replAction ( configFlags, configExFlags, installFlags
252
252
withInstallPlan (lessVerbose verbosity) baseCtx $ \ elaboratedPlan _ -> do
253
253
-- targets should be non-empty map, but there's no NonEmptyMap yet.
254
254
targets <- validatedTargets elaboratedPlan targetSelectors
255
-
255
+
256
256
let
257
257
(unitId, _) = fromMaybe (error " panic: targets should be non-empty" ) $ safeHead $ Map. toList targets
258
258
originalDeps = installedUnitId <$> InstallPlan. directDeps elaboratedPlan unitId
259
259
oci = OriginalComponentInfo unitId originalDeps
260
- pkgId = fromMaybe (error $ " cannot find " ++ prettyShow unitId) $ packageId <$> InstallPlan. lookup elaboratedPlan unitId
260
+ pkgId = fromMaybe (error $ " cannot find " ++ prettyShow unitId) $ packageId <$> InstallPlan. lookup elaboratedPlan unitId
261
261
baseCtx' = addDepsToProjectTarget (envPackages envFlags) pkgId baseCtx
262
262
263
263
return (Just oci, baseCtx')
264
-
265
- -- Now, we run the solver again with the added packages. While the graph
264
+
265
+ -- Now, we run the solver again with the added packages. While the graph
266
266
-- won't actually reflect the addition of transitive dependencies,
267
267
-- they're going to be available already and will be offered to the REPL
268
268
-- and that's good enough.
269
269
--
270
- -- In addition, to avoid a *third* trip through the solver, we are
270
+ -- In addition, to avoid a *third* trip through the solver, we are
271
271
-- replicating the second half of 'runProjectPreBuildPhase' by hand
272
272
-- here.
273
273
(buildCtx, replFlags'') <- withInstallPlan verbosity baseCtx' $
274
274
\ elaboratedPlan elaboratedShared' -> do
275
275
let ProjectBaseContext {.. } = baseCtx'
276
-
276
+
277
277
-- Recalculate with updated project.
278
278
targets <- validatedTargets elaboratedPlan targetSelectors
279
279
280
- let
280
+ let
281
281
elaboratedPlan' = pruneInstallPlanToTargets
282
282
TargetActionRepl
283
283
targets
284
284
elaboratedPlan
285
285
includeTransitive = fromFlagOrDefault True (envIncludeTransitive envFlags)
286
-
286
+
287
287
pkgsBuildStatus <- rebuildTargetsDryRun distDirLayout elaboratedShared'
288
288
elaboratedPlan'
289
289
290
290
let elaboratedPlan'' = improveInstallPlanWithUpToDatePackages
291
291
pkgsBuildStatus elaboratedPlan'
292
292
debugNoWrap verbosity (InstallPlan. showInstallPlan elaboratedPlan'')
293
293
294
- let
295
- buildCtx = ProjectBuildContext
294
+ let
295
+ buildCtx = ProjectBuildContext
296
296
{ elaboratedPlanOriginal = elaboratedPlan
297
297
, elaboratedPlanToExecute = elaboratedPlan''
298
298
, elaboratedShared = elaboratedShared'
299
299
, pkgsBuildStatus
300
300
, targetsMap = targets
301
301
}
302
-
302
+
303
303
ElaboratedSharedConfig { pkgConfigCompiler = compiler } = elaboratedShared'
304
-
304
+
305
305
-- First version of GHC where GHCi supported the flag we need.
306
306
-- https://downloads.haskell.org/~ghc/7.6.1/docs/html/users_guide/release-7-6-1.html
307
307
minGhciScriptVersion = mkVersion [7 , 6 ]
308
308
309
- replFlags' = case originalComponent of
309
+ replFlags' = case originalComponent of
310
310
Just oci -> generateReplFlags includeTransitive elaboratedPlan' oci
311
311
Nothing -> []
312
312
replFlags'' = case replType of
313
- GlobalRepl scriptPath
313
+ GlobalRepl scriptPath
314
314
| Just version <- compilerCompatVersion GHC compiler
315
315
, version >= minGhciScriptVersion -> (" -ghci-script" ++ scriptPath) : replFlags'
316
316
_ -> replFlags'
@@ -334,7 +334,7 @@ replAction ( configFlags, configExFlags, installFlags
334
334
mempty -- ClientInstallFlags, not needed here
335
335
haddockFlags testFlags benchmarkFlags
336
336
globalConfigFlag = projectConfigConfigFile (projectConfigShared cliConfig)
337
-
337
+
338
338
validatedTargets elaboratedPlan targetSelectors = do
339
339
-- Interpret the targets on the command line as repl targets
340
340
-- (as opposed to say build or haddock targets).
@@ -363,7 +363,7 @@ data OriginalComponentInfo = OriginalComponentInfo
363
363
deriving (Show )
364
364
365
365
-- | Tracks what type of GHCi instance we're creating.
366
- data ReplType = ProjectRepl
366
+ data ReplType = ProjectRepl
367
367
| GlobalRepl FilePath -- ^ The 'FilePath' argument is path to a GHCi
368
368
-- script responsible for changing to the
369
369
-- correct directory. Only works on GHC geq
@@ -397,7 +397,7 @@ withoutProject config verbosity extraArgs = do
397
397
, packageSource = LocalUnpackedPackage tempDir
398
398
, packageDescrOverride = Nothing
399
399
}
400
- genericPackageDescription = emptyGenericPackageDescription
400
+ genericPackageDescription = emptyGenericPackageDescription
401
401
& L. packageDescription .~ packageDescription
402
402
& L. condLibrary .~ Just (CondNode library [baseDep] [] )
403
403
packageDescription = emptyPackageDescription
@@ -414,13 +414,13 @@ withoutProject config verbosity extraArgs = do
414
414
pkgId = fakePackageId
415
415
416
416
writeGenericPackageDescription (tempDir </> " fake-package.cabal" ) genericPackageDescription
417
-
417
+
418
418
let ghciScriptPath = tempDir </> " setcwd.ghci"
419
419
cwd <- getCurrentDirectory
420
420
writeFile ghciScriptPath (" :cd " ++ cwd)
421
421
422
422
distDirLayout <- establishDummyDistDirLayout verbosity config tempDir
423
- baseCtx <-
423
+ baseCtx <-
424
424
establishDummyProjectBaseContext
425
425
verbosity
426
426
config
@@ -438,15 +438,15 @@ addDepsToProjectTarget :: [Dependency]
438
438
-> PackageId
439
439
-> ProjectBaseContext
440
440
-> ProjectBaseContext
441
- addDepsToProjectTarget deps pkgId ctx =
441
+ addDepsToProjectTarget deps pkgId ctx =
442
442
(\ p -> ctx { localPackages = p }) . fmap addDeps . localPackages $ ctx
443
443
where
444
444
addDeps :: PackageSpecifier UnresolvedSourcePackage
445
445
-> PackageSpecifier UnresolvedSourcePackage
446
446
addDeps (SpecificSourcePackage pkg)
447
447
| packageId pkg /= pkgId = SpecificSourcePackage pkg
448
448
| SourcePackage {.. } <- pkg =
449
- SpecificSourcePackage $ pkg { packageDescription =
449
+ SpecificSourcePackage $ pkg { packageDescription =
450
450
packageDescription & (\ f -> L. allCondTrees $ traverseCondTreeC f)
451
451
%~ (deps ++ )
452
452
}
@@ -456,8 +456,8 @@ generateReplFlags :: Bool -> ElaboratedInstallPlan -> OriginalComponentInfo -> R
456
456
generateReplFlags includeTransitive elaboratedPlan OriginalComponentInfo {.. } = flags
457
457
where
458
458
exeDeps :: [UnitId ]
459
- exeDeps =
460
- foldMap
459
+ exeDeps =
460
+ foldMap
461
461
(InstallPlan. foldPlanPackage (const [] ) elabOrderExeDependencies)
462
462
(InstallPlan. dependencyClosure elaboratedPlan [ociUnitId])
463
463
@@ -621,4 +621,3 @@ explanationSingleComponentLimitation =
621
621
" The reason for this limitation is that current versions of ghci do not "
622
622
++ " support loading multiple components as source. Load just one component "
623
623
++ " and when you make changes to a dependent component then quit and reload."
624
-
0 commit comments