Skip to content

Commit 85d9acf

Browse files
committed
update --build-depends help string
1 parent 9894516 commit 85d9acf

File tree

1 file changed

+28
-29
lines changed

1 file changed

+28
-29
lines changed

cabal-install/Distribution/Client/CmdRepl.hs

Lines changed: 28 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ import Distribution.Client.ProjectConfig
3131
( ProjectConfig(..), withProjectOrGlobalConfigIgn
3232
, projectConfigConfigFile )
3333
import Distribution.Client.ProjectOrchestration
34-
import Distribution.Client.ProjectPlanning
34+
import Distribution.Client.ProjectPlanning
3535
( ElaboratedSharedConfig(..), ElaboratedInstallPlan )
3636
import Distribution.Client.ProjectPlanning.Types
3737
( elabOrderExeDependencies )
@@ -109,7 +109,7 @@ import System.FilePath
109109

110110
type ReplFlags = [String]
111111

112-
data EnvFlags = EnvFlags
112+
data EnvFlags = EnvFlags
113113
{ envPackages :: [Dependency]
114114
, envIncludeTransitive :: Flag Bool
115115
, envIgnoreProject :: Flag Bool
@@ -125,9 +125,9 @@ defaultEnvFlags = EnvFlags
125125
envOptions :: ShowOrParseArgs -> [OptionField EnvFlags]
126126
envOptions _ =
127127
[ 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."
129129
envPackages (\p flags -> flags { envPackages = p ++ envPackages flags })
130-
(reqArg "DEPENDENCY" dependencyReadE (fmap prettyShow :: [Dependency] -> [String]))
130+
(reqArg "DEPENDENCIES" dependencyReadE (fmap prettyShow :: [Dependency] -> [String]))
131131
, option [] ["no-transitive-deps"]
132132
"Don't automatically include transitive dependencies of requested packages."
133133
envIncludeTransitive (\p flags -> flags { envIncludeTransitive = p })
@@ -234,7 +234,7 @@ replAction ( configFlags, configExFlags, installFlags
234234
ignoreProject = fromFlagOrDefault False (envIgnoreProject envFlags)
235235
with = withProject cliConfig verbosity targetStrings
236236
without config = withoutProject (config <> cliConfig) verbosity targetStrings
237-
237+
238238
(baseCtx, targetSelectors, finalizer, replType) <-
239239
withProjectOrGlobalConfigIgn ignoreProject verbosity globalConfigFlag with without
240240

@@ -252,65 +252,65 @@ replAction ( configFlags, configExFlags, installFlags
252252
withInstallPlan (lessVerbose verbosity) baseCtx $ \elaboratedPlan _ -> do
253253
-- targets should be non-empty map, but there's no NonEmptyMap yet.
254254
targets <- validatedTargets elaboratedPlan targetSelectors
255-
255+
256256
let
257257
(unitId, _) = fromMaybe (error "panic: targets should be non-empty") $ safeHead $ Map.toList targets
258258
originalDeps = installedUnitId <$> InstallPlan.directDeps elaboratedPlan unitId
259259
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
261261
baseCtx' = addDepsToProjectTarget (envPackages envFlags) pkgId baseCtx
262262

263263
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
266266
-- won't actually reflect the addition of transitive dependencies,
267267
-- they're going to be available already and will be offered to the REPL
268268
-- and that's good enough.
269269
--
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
271271
-- replicating the second half of 'runProjectPreBuildPhase' by hand
272272
-- here.
273273
(buildCtx, replFlags'') <- withInstallPlan verbosity baseCtx' $
274274
\elaboratedPlan elaboratedShared' -> do
275275
let ProjectBaseContext{..} = baseCtx'
276-
276+
277277
-- Recalculate with updated project.
278278
targets <- validatedTargets elaboratedPlan targetSelectors
279279

280-
let
280+
let
281281
elaboratedPlan' = pruneInstallPlanToTargets
282282
TargetActionRepl
283283
targets
284284
elaboratedPlan
285285
includeTransitive = fromFlagOrDefault True (envIncludeTransitive envFlags)
286-
286+
287287
pkgsBuildStatus <- rebuildTargetsDryRun distDirLayout elaboratedShared'
288288
elaboratedPlan'
289289

290290
let elaboratedPlan'' = improveInstallPlanWithUpToDatePackages
291291
pkgsBuildStatus elaboratedPlan'
292292
debugNoWrap verbosity (InstallPlan.showInstallPlan elaboratedPlan'')
293293

294-
let
295-
buildCtx = ProjectBuildContext
294+
let
295+
buildCtx = ProjectBuildContext
296296
{ elaboratedPlanOriginal = elaboratedPlan
297297
, elaboratedPlanToExecute = elaboratedPlan''
298298
, elaboratedShared = elaboratedShared'
299299
, pkgsBuildStatus
300300
, targetsMap = targets
301301
}
302-
302+
303303
ElaboratedSharedConfig { pkgConfigCompiler = compiler } = elaboratedShared'
304-
304+
305305
-- First version of GHC where GHCi supported the flag we need.
306306
-- https://downloads.haskell.org/~ghc/7.6.1/docs/html/users_guide/release-7-6-1.html
307307
minGhciScriptVersion = mkVersion [7, 6]
308308

309-
replFlags' = case originalComponent of
309+
replFlags' = case originalComponent of
310310
Just oci -> generateReplFlags includeTransitive elaboratedPlan' oci
311311
Nothing -> []
312312
replFlags'' = case replType of
313-
GlobalRepl scriptPath
313+
GlobalRepl scriptPath
314314
| Just version <- compilerCompatVersion GHC compiler
315315
, version >= minGhciScriptVersion -> ("-ghci-script" ++ scriptPath) : replFlags'
316316
_ -> replFlags'
@@ -334,7 +334,7 @@ replAction ( configFlags, configExFlags, installFlags
334334
mempty -- ClientInstallFlags, not needed here
335335
haddockFlags testFlags benchmarkFlags
336336
globalConfigFlag = projectConfigConfigFile (projectConfigShared cliConfig)
337-
337+
338338
validatedTargets elaboratedPlan targetSelectors = do
339339
-- Interpret the targets on the command line as repl targets
340340
-- (as opposed to say build or haddock targets).
@@ -363,7 +363,7 @@ data OriginalComponentInfo = OriginalComponentInfo
363363
deriving (Show)
364364

365365
-- | Tracks what type of GHCi instance we're creating.
366-
data ReplType = ProjectRepl
366+
data ReplType = ProjectRepl
367367
| GlobalRepl FilePath -- ^ The 'FilePath' argument is path to a GHCi
368368
-- script responsible for changing to the
369369
-- correct directory. Only works on GHC geq
@@ -397,7 +397,7 @@ withoutProject config verbosity extraArgs = do
397397
, packageSource = LocalUnpackedPackage tempDir
398398
, packageDescrOverride = Nothing
399399
}
400-
genericPackageDescription = emptyGenericPackageDescription
400+
genericPackageDescription = emptyGenericPackageDescription
401401
& L.packageDescription .~ packageDescription
402402
& L.condLibrary .~ Just (CondNode library [baseDep] [])
403403
packageDescription = emptyPackageDescription
@@ -414,13 +414,13 @@ withoutProject config verbosity extraArgs = do
414414
pkgId = fakePackageId
415415

416416
writeGenericPackageDescription (tempDir </> "fake-package.cabal") genericPackageDescription
417-
417+
418418
let ghciScriptPath = tempDir </> "setcwd.ghci"
419419
cwd <- getCurrentDirectory
420420
writeFile ghciScriptPath (":cd " ++ cwd)
421421

422422
distDirLayout <- establishDummyDistDirLayout verbosity config tempDir
423-
baseCtx <-
423+
baseCtx <-
424424
establishDummyProjectBaseContext
425425
verbosity
426426
config
@@ -438,15 +438,15 @@ addDepsToProjectTarget :: [Dependency]
438438
-> PackageId
439439
-> ProjectBaseContext
440440
-> ProjectBaseContext
441-
addDepsToProjectTarget deps pkgId ctx =
441+
addDepsToProjectTarget deps pkgId ctx =
442442
(\p -> ctx { localPackages = p }) . fmap addDeps . localPackages $ ctx
443443
where
444444
addDeps :: PackageSpecifier UnresolvedSourcePackage
445445
-> PackageSpecifier UnresolvedSourcePackage
446446
addDeps (SpecificSourcePackage pkg)
447447
| packageId pkg /= pkgId = SpecificSourcePackage pkg
448448
| SourcePackage{..} <- pkg =
449-
SpecificSourcePackage $ pkg { packageDescription =
449+
SpecificSourcePackage $ pkg { packageDescription =
450450
packageDescription & (\f -> L.allCondTrees $ traverseCondTreeC f)
451451
%~ (deps ++)
452452
}
@@ -456,8 +456,8 @@ generateReplFlags :: Bool -> ElaboratedInstallPlan -> OriginalComponentInfo -> R
456456
generateReplFlags includeTransitive elaboratedPlan OriginalComponentInfo{..} = flags
457457
where
458458
exeDeps :: [UnitId]
459-
exeDeps =
460-
foldMap
459+
exeDeps =
460+
foldMap
461461
(InstallPlan.foldPlanPackage (const []) elabOrderExeDependencies)
462462
(InstallPlan.dependencyClosure elaboratedPlan [ociUnitId])
463463

@@ -621,4 +621,3 @@ explanationSingleComponentLimitation =
621621
"The reason for this limitation is that current versions of ghci do not "
622622
++ "support loading multiple components as source. Load just one component "
623623
++ "and when you make changes to a dependent component then quit and reload."
624-

0 commit comments

Comments
 (0)