@@ -106,7 +106,8 @@ import Distribution.Simple.Compiler
106106 )
107107import Distribution.Simple.Program.GHC
108108import Distribution.Simple.Setup
109- ( ReplOptions (.. )
109+ ( Flag
110+ , ReplOptions (.. )
110111 , commonSetupTempFileOptions
111112 )
112113import Distribution.Simple.Utils
@@ -170,8 +171,8 @@ import Data.List
170171import qualified Data.Map as Map
171172import qualified Data.Set as Set
172173import Distribution.Client.ProjectConfig
173- ( ProjectConfig (projectConfigShared )
174- , ProjectConfigShared (projectConfigConstraints , projectConfigMultiRepl )
174+ ( ProjectConfig (.. )
175+ , ProjectConfigShared (.. )
175176 )
176177import Distribution.Client.ReplFlags
177178 ( EnvFlags (envIncludeTransitive , envPackages )
@@ -184,6 +185,7 @@ import Distribution.Simple.Flag (flagToMaybe, fromFlagOrDefault, pattern Flag)
184185import Distribution.Simple.Program.Builtin (ghcProgram )
185186import Distribution.Simple.Program.Db (requireProgram )
186187import Distribution.Simple.Program.Types
188+ import Distribution.Types.PackageName.Magic (fakePackageId )
187189import System.Directory
188190 ( doesFileExist
189191 , getCurrentDirectory
@@ -195,6 +197,7 @@ import System.FilePath
195197 , splitSearchPath
196198 , (</>)
197199 )
200+ import Text.PrettyPrint hiding ((<>) )
198201
199202replCommand :: CommandUI (NixStyleFlags ReplFlags )
200203replCommand =
@@ -281,17 +284,30 @@ multiReplDecision ctx compiler flags =
281284-- For more details on how this works, see the module
282285-- "Distribution.Client.ProjectOrchestration"
283286replAction :: NixStyleFlags ReplFlags -> [String ] -> GlobalFlags -> IO ()
284- replAction flags@ NixStyleFlags {extraFlags = r @ ReplFlags {.. }, .. } targetStrings globalFlags =
285- withContextAndSelectors verbosity AcceptNoTargets ( Just LibKind ) flags targetStrings globalFlags ReplCommand $ \ targetCtx ctx targetSelectors -> do
287+ replAction flags@ NixStyleFlags {extraFlags = replFlags @ ReplFlags {.. }, configFlags } targetStrings globalFlags = do
288+ withCtx verbosity targetStrings $ \ targetCtx ctx userTargetSelectors -> do
286289 when (buildSettingOnlyDeps (buildSettings ctx)) $
287290 dieWithException verbosity ReplCommandDoesn'tSupport
288291 let projectRoot = distProjectRootDirectory $ distDirLayout ctx
289292 distDir = distDirectory $ distDirLayout ctx
290293
291- baseCtx <- case targetCtx of
292- ProjectContext -> return ctx
294+ -- After ther user selectors have been resolved, and it's decided what context
295+ -- we're in, implement repl-specific behaviour.
296+ (baseCtx, targetSelectors) <- case targetCtx of
297+ -- If in the project context, and no selectors are provided
298+ -- then produce an error.
299+ ProjectContext -> do
300+ let projectFile = projectConfigProjectFile . projectConfigShared $ projectConfig ctx
301+ let pkgs = projectPackages $ projectConfig ctx
302+ case userTargetSelectors of
303+ [] ->
304+ dieWithException verbosity $
305+ RenderReplTargetProblem [render (reportProjectNoTarget projectFile pkgs)]
306+ _ -> return (ctx, userTargetSelectors)
307+ -- In the global context, construct a fake package which can be used to start
308+ -- a repl with extra arguments if `-b` is given.
293309 GlobalContext -> do
294- unless (null targetStrings ) $
310+ unless (null userTargetSelectors ) $
295311 dieWithException verbosity $
296312 ReplTakesNoArguments targetStrings
297313 let
@@ -303,12 +319,18 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
303319 library = emptyLibrary{libBuildInfo = lBuildInfo}
304320 lBuildInfo =
305321 emptyBuildInfo
306- { targetBuildDepends = [baseDep]
322+ { targetBuildDepends = [baseDep] ++ envPackages replEnvFlags
307323 , defaultLanguage = Just Haskell2010
308324 }
309325 baseDep = Dependency " base" anyVersion mainLibSet
310326
311- updateContextAndWriteProjectFile' ctx sourcePackage
327+ -- Write the fake package
328+ updatedCtx <- updateContextAndWriteProjectFile' ctx sourcePackage
329+ -- Specify the selector for this package
330+ let fakeSelector = TargetPackage TargetExplicitNamed [fakePackageId] Nothing
331+ return (updatedCtx, [fakeSelector])
332+
333+ -- For the script context, no special behaviour.
312334 ScriptContext scriptPath scriptExecutable -> do
313335 unless (length targetStrings == 1 ) $
314336 dieWithException verbosity $
@@ -318,7 +340,8 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
318340 dieWithException verbosity $
319341 ReplTakesSingleArgument targetStrings
320342
321- updateContextAndWriteProjectFile ctx scriptPath scriptExecutable
343+ updatedCtx <- updateContextAndWriteProjectFile ctx scriptPath scriptExecutable
344+ return (updatedCtx, userTargetSelectors)
322345
323346 -- If multi-repl is used, we need a Cabal recent enough to handle it.
324347 -- We need to do this before solving, but the compiler version is only known
@@ -361,7 +384,7 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
361384 -- especially in the no-project case.
362385 withInstallPlan (lessVerbose verbosity) baseCtx' $ \ elaboratedPlan sharedConfig -> do
363386 -- targets should be non-empty map, but there's no NonEmptyMap yet.
364- targets <- validatedTargets (projectConfigShared (projectConfig ctx)) (pkgConfigCompiler sharedConfig) elaboratedPlan targetSelectors
387+ targets <- validatedTargets' (projectConfigShared (projectConfig ctx)) (pkgConfigCompiler sharedConfig) elaboratedPlan targetSelectors
365388
366389 let
367390 (unitId, _) = fromMaybe (error " panic: targets should be non-empty" ) $ safeHead $ Map. toList targets
@@ -385,7 +408,7 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
385408 let ProjectBaseContext {.. } = baseCtx''
386409
387410 -- Recalculate with updated project.
388- targets <- validatedTargets (projectConfigShared projectConfig) (pkgConfigCompiler elaboratedShared') elaboratedPlan targetSelectors
411+ targets <- validatedTargets' (projectConfigShared projectConfig) (pkgConfigCompiler elaboratedShared') elaboratedPlan targetSelectors
389412
390413 let
391414 elaboratedPlan' =
@@ -518,31 +541,13 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
518541 go m (" PATH" , Just s) = foldl' (\ m' f -> Map. insertWith (+) f 1 m') m (splitSearchPath s)
519542 go m _ = m
520543
544+ withCtx ctxVerbosity strings =
545+ withContextAndSelectors ctxVerbosity AcceptNoTargets (Just LibKind ) flags strings globalFlags ReplCommand
546+
521547 verbosity = cfgVerbosity normal flags
522548 tempFileOptions = commonSetupTempFileOptions $ configCommonFlags configFlags
523549
524- validatedTargets ctx compiler elaboratedPlan targetSelectors = do
525- let multi_repl_enabled = multiReplDecision ctx compiler r
526- -- Interpret the targets on the command line as repl targets
527- -- (as opposed to say build or haddock targets).
528- targets <-
529- either (reportTargetProblems verbosity) return $
530- resolveTargetsFromSolver
531- (selectPackageTargets multi_repl_enabled)
532- selectComponentTarget
533- elaboratedPlan
534- Nothing
535- targetSelectors
536-
537- -- Reject multiple targets, or at least targets in different
538- -- components. It is ok to have two module/file targets in the
539- -- same component, but not two that live in different components.
540- when (Set. size (distinctTargetComponents targets) > 1 && not (useMultiRepl multi_repl_enabled)) $
541- reportTargetProblems
542- verbosity
543- [multipleTargetsProblem multi_repl_enabled targets]
544-
545- return targets
550+ validatedTargets' = validatedTargets verbosity replFlags
546551
547552-- | Create a constraint which requires a later version of Cabal.
548553-- This is used for commands which require a specific feature from the Cabal library
@@ -555,6 +560,69 @@ requireCabal version source =
555560 , source
556561 )
557562
563+ reportProjectNoTarget :: Flag FilePath -> [String ] -> Doc
564+ reportProjectNoTarget projectFile pkgs =
565+ case (null pkgs, projectName) of
566+ (True , Just project) ->
567+ text " There are no packages in"
568+ <+> (project <> char ' .' )
569+ <+> text " Please add a package to the project and"
570+ <+> pickComponent
571+ (True , Nothing ) ->
572+ text " Please add a package to the project and" <+> pickComponent
573+ (False , Just project) ->
574+ text " Please"
575+ <+> pickComponent
576+ <+> text " The packages in"
577+ <+> project
578+ <+> (text " from which to select a component target are" <> colon)
579+ $+$ nest 1 (vcat [text " -" <+> text pkg | pkg <- sort pkgs])
580+ (False , Nothing ) ->
581+ text " Please"
582+ <+> pickComponent
583+ <+> (text " The packages from which to select a component in 'cabal.project'" <> comma)
584+ <+> (text " the implicit default as if `--project-file=cabal.project` was added as a command option" <> comma)
585+ <+> (text " are" <> colon)
586+ $+$ nest 1 (vcat [text " -" <+> text pkg | pkg <- sort pkgs])
587+ where
588+ projectName = case projectFile of
589+ Flag " " -> Nothing
590+ Flag n -> Just $ quotes (text n)
591+ _ -> Nothing
592+ pickComponent = text " pick a single [package:][ctype:]component (or all) as target for the REPL command."
593+
594+ -- | Invariant: validatedTargets returns at least one target for the REPL.
595+ validatedTargets
596+ :: Verbosity
597+ -> ReplFlags
598+ -> ProjectConfigShared
599+ -> Compiler
600+ -> ElaboratedInstallPlan
601+ -> [TargetSelector ]
602+ -> IO TargetsMap
603+ validatedTargets verbosity replFlags ctx compiler elaboratedPlan targetSelectors = do
604+ let multi_repl_enabled = multiReplDecision ctx compiler replFlags
605+ -- Interpret the targets on the command line as repl targets (as opposed to
606+ -- say build or haddock targets).
607+ targets <-
608+ either (reportTargetProblems verbosity) return $
609+ resolveTargetsFromSolver
610+ (selectPackageTargets multi_repl_enabled)
611+ selectComponentTarget
612+ elaboratedPlan
613+ Nothing
614+ targetSelectors
615+
616+ -- Reject multiple targets, or at least targets in different components. It is
617+ -- ok to have two module/file targets in the same component, but not two that
618+ -- live in different components.
619+ when (Set. size (distinctTargetComponents targets) > 1 && not (useMultiRepl multi_repl_enabled)) $
620+ reportTargetProblems
621+ verbosity
622+ [multipleTargetsProblem multi_repl_enabled targets]
623+
624+ return targets
625+
558626-- | First version of GHC which supports multiple home packages
559627minMultipleHomeUnitsVersion :: Version
560628minMultipleHomeUnitsVersion = mkVersion [9 , 4 ]
0 commit comments