Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
138 changes: 103 additions & 35 deletions cabal-install/src/Distribution/Client/CmdRepl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,8 @@ import Distribution.Simple.Compiler
)
import Distribution.Simple.Program.GHC
import Distribution.Simple.Setup
( ReplOptions (..)
( Flag
, ReplOptions (..)
, commonSetupTempFileOptions
)
import Distribution.Simple.Utils
Expand Down Expand Up @@ -170,8 +171,8 @@ import Data.List
import qualified Data.Map as Map
import qualified Data.Set as Set
import Distribution.Client.ProjectConfig
( ProjectConfig (projectConfigShared)
, ProjectConfigShared (projectConfigConstraints, projectConfigMultiRepl)
( ProjectConfig (..)
, ProjectConfigShared (..)
)
import Distribution.Client.ReplFlags
( EnvFlags (envIncludeTransitive, envPackages)
Expand All @@ -184,6 +185,7 @@ import Distribution.Simple.Flag (flagToMaybe, fromFlagOrDefault, pattern Flag)
import Distribution.Simple.Program.Builtin (ghcProgram)
import Distribution.Simple.Program.Db (requireProgram)
import Distribution.Simple.Program.Types
import Distribution.Types.PackageName.Magic (fakePackageId)
import System.Directory
( doesFileExist
, getCurrentDirectory
Expand All @@ -195,6 +197,7 @@ import System.FilePath
, splitSearchPath
, (</>)
)
import Text.PrettyPrint hiding ((<>))

replCommand :: CommandUI (NixStyleFlags ReplFlags)
replCommand =
Expand Down Expand Up @@ -281,17 +284,30 @@ multiReplDecision ctx compiler flags =
-- For more details on how this works, see the module
-- "Distribution.Client.ProjectOrchestration"
replAction :: NixStyleFlags ReplFlags -> [String] -> GlobalFlags -> IO ()
replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings globalFlags =
withContextAndSelectors verbosity AcceptNoTargets (Just LibKind) flags targetStrings globalFlags ReplCommand $ \targetCtx ctx targetSelectors -> do
replAction flags@NixStyleFlags{extraFlags = replFlags@ReplFlags{..}, configFlags} targetStrings globalFlags = do
withCtx verbosity targetStrings $ \targetCtx ctx userTargetSelectors -> do
when (buildSettingOnlyDeps (buildSettings ctx)) $
dieWithException verbosity ReplCommandDoesn'tSupport
let projectRoot = distProjectRootDirectory $ distDirLayout ctx
distDir = distDirectory $ distDirLayout ctx

baseCtx <- case targetCtx of
ProjectContext -> return ctx
-- After ther user selectors have been resolved, and it's decided what context
-- we're in, implement repl-specific behaviour.
(baseCtx, targetSelectors) <- case targetCtx of
-- If in the project context, and no selectors are provided
-- then produce an error.
ProjectContext -> do
let projectFile = projectConfigProjectFile . projectConfigShared $ projectConfig ctx
let pkgs = projectPackages $ projectConfig ctx
case userTargetSelectors of
[] ->
dieWithException verbosity $
RenderReplTargetProblem [render (reportProjectNoTarget projectFile pkgs)]
_ -> return (ctx, userTargetSelectors)
-- In the global context, construct a fake package which can be used to start
-- a repl with extra arguments if `-b` is given.
GlobalContext -> do
unless (null targetStrings) $
unless (null userTargetSelectors) $
dieWithException verbosity $
ReplTakesNoArguments targetStrings
let
Expand All @@ -303,12 +319,18 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
library = emptyLibrary{libBuildInfo = lBuildInfo}
lBuildInfo =
emptyBuildInfo
{ targetBuildDepends = [baseDep]
{ targetBuildDepends = [baseDep] ++ envPackages replEnvFlags
, defaultLanguage = Just Haskell2010
}
baseDep = Dependency "base" anyVersion mainLibSet

updateContextAndWriteProjectFile' ctx sourcePackage
-- Write the fake package
updatedCtx <- updateContextAndWriteProjectFile' ctx sourcePackage
-- Specify the selector for this package
let fakeSelector = TargetPackage TargetExplicitNamed [fakePackageId] Nothing
return (updatedCtx, [fakeSelector])

-- For the script context, no special behaviour.
ScriptContext scriptPath scriptExecutable -> do
unless (length targetStrings == 1) $
dieWithException verbosity $
Expand All @@ -318,7 +340,8 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
dieWithException verbosity $
ReplTakesSingleArgument targetStrings

updateContextAndWriteProjectFile ctx scriptPath scriptExecutable
updatedCtx <- updateContextAndWriteProjectFile ctx scriptPath scriptExecutable
return (updatedCtx, userTargetSelectors)

-- If multi-repl is used, we need a Cabal recent enough to handle it.
-- We need to do this before solving, but the compiler version is only known
Expand Down Expand Up @@ -361,7 +384,7 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
-- especially in the no-project case.
withInstallPlan (lessVerbose verbosity) baseCtx' $ \elaboratedPlan sharedConfig -> do
-- targets should be non-empty map, but there's no NonEmptyMap yet.
targets <- validatedTargets (projectConfigShared (projectConfig ctx)) (pkgConfigCompiler sharedConfig) elaboratedPlan targetSelectors
targets <- validatedTargets' (projectConfigShared (projectConfig ctx)) (pkgConfigCompiler sharedConfig) elaboratedPlan targetSelectors

let
(unitId, _) = fromMaybe (error "panic: targets should be non-empty") $ safeHead $ Map.toList targets
Expand All @@ -385,7 +408,7 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
let ProjectBaseContext{..} = baseCtx''

-- Recalculate with updated project.
targets <- validatedTargets (projectConfigShared projectConfig) (pkgConfigCompiler elaboratedShared') elaboratedPlan targetSelectors
targets <- validatedTargets' (projectConfigShared projectConfig) (pkgConfigCompiler elaboratedShared') elaboratedPlan targetSelectors

let
elaboratedPlan' =
Expand Down Expand Up @@ -518,31 +541,13 @@ replAction flags@NixStyleFlags{extraFlags = r@ReplFlags{..}, ..} targetStrings g
go m ("PATH", Just s) = foldl' (\m' f -> Map.insertWith (+) f 1 m') m (splitSearchPath s)
go m _ = m

withCtx ctxVerbosity strings =
withContextAndSelectors ctxVerbosity AcceptNoTargets (Just LibKind) flags strings globalFlags ReplCommand

verbosity = cfgVerbosity normal flags
tempFileOptions = commonSetupTempFileOptions $ configCommonFlags configFlags

validatedTargets ctx compiler elaboratedPlan targetSelectors = do
let multi_repl_enabled = multiReplDecision ctx compiler r
-- Interpret the targets on the command line as repl targets
-- (as opposed to say build or haddock targets).
targets <-
either (reportTargetProblems verbosity) return $
resolveTargetsFromSolver
(selectPackageTargets multi_repl_enabled)
selectComponentTarget
elaboratedPlan
Nothing
targetSelectors

-- Reject multiple targets, or at least targets in different
-- components. It is ok to have two module/file targets in the
-- same component, but not two that live in different components.
when (Set.size (distinctTargetComponents targets) > 1 && not (useMultiRepl multi_repl_enabled)) $
reportTargetProblems
verbosity
[multipleTargetsProblem multi_repl_enabled targets]

return targets
validatedTargets' = validatedTargets verbosity replFlags

-- | Create a constraint which requires a later version of Cabal.
-- This is used for commands which require a specific feature from the Cabal library
Expand All @@ -555,6 +560,69 @@ requireCabal version source =
, source
)

reportProjectNoTarget :: Flag FilePath -> [String] -> Doc
reportProjectNoTarget projectFile pkgs =
case (null pkgs, projectName) of
(True, Just project) ->
text "There are no packages in"
<+> (project <> char '.')
<+> text "Please add a package to the project and"
<+> pickComponent
(True, Nothing) ->
text "Please add a package to the project and" <+> pickComponent
(False, Just project) ->
text "Please"
<+> pickComponent
<+> text "The packages in"
<+> project
<+> (text "from which to select a component target are" <> colon)
$+$ nest 1 (vcat [text "-" <+> text pkg | pkg <- sort pkgs])
(False, Nothing) ->
text "Please"
<+> pickComponent
<+> (text "The packages from which to select a component in 'cabal.project'" <> comma)
<+> (text "the implicit default as if `--project-file=cabal.project` was added as a command option" <> comma)
<+> (text "are" <> colon)
$+$ nest 1 (vcat [text "-" <+> text pkg | pkg <- sort pkgs])
where
projectName = case projectFile of
Flag "" -> Nothing
Flag n -> Just $ quotes (text n)
_ -> Nothing
pickComponent = text "pick a single [package:][ctype:]component (or all) as target for the REPL command."

-- | Invariant: validatedTargets returns at least one target for the REPL.
validatedTargets
:: Verbosity
-> ReplFlags
-> ProjectConfigShared
-> Compiler
-> ElaboratedInstallPlan
-> [TargetSelector]
-> IO TargetsMap
validatedTargets verbosity replFlags ctx compiler elaboratedPlan targetSelectors = do
let multi_repl_enabled = multiReplDecision ctx compiler replFlags
-- Interpret the targets on the command line as repl targets (as opposed to
-- say build or haddock targets).
targets <-
either (reportTargetProblems verbosity) return $
resolveTargetsFromSolver
(selectPackageTargets multi_repl_enabled)
selectComponentTarget
elaboratedPlan
Nothing
targetSelectors

-- Reject multiple targets, or at least targets in different components. It is
-- ok to have two module/file targets in the same component, but not two that
-- live in different components.
when (Set.size (distinctTargetComponents targets) > 1 && not (useMultiRepl multi_repl_enabled)) $
reportTargetProblems
verbosity
[multipleTargetsProblem multi_repl_enabled targets]

return targets

-- | First version of GHC which supports multiple home packages
minMultipleHomeUnitsVersion :: Version
minMultipleHomeUnitsVersion = mkVersion [9, 4]
Expand Down
1 change: 1 addition & 0 deletions cabal-testsuite/PackageTests/ReplDashB/File.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
module File where
8 changes: 8 additions & 0 deletions cabal-testsuite/PackageTests/ReplDashB/cabal.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
# cabal clean
# cabal v2-repl
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- fake-package-0 (interactive) (lib) (first run)
Configuring library for fake-package-0...
Warning: No exposed modules
8 changes: 8 additions & 0 deletions cabal-testsuite/PackageTests/ReplDashB/cabal.test.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
import Test.Cabal.Prelude

main = do
cabalTest $ do
cabal' "clean" []
res <- cabalWithStdin "v2-repl" ["-b", "containers"] ":m +Data.Map\n:t fromList"
assertOutputContains "fromList :: Ord k => [(k, a)] -> Map k a" res

1 change: 1 addition & 0 deletions cabal-testsuite/PackageTests/ReplOptions/alt.project
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: alt
4 changes: 4 additions & 0 deletions cabal-testsuite/PackageTests/ReplOptions/alt/ModuleA.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module ModuleA where

a :: Int
a = 42
4 changes: 4 additions & 0 deletions cabal-testsuite/PackageTests/ReplOptions/alt/ModuleC.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module ModuleC where

c :: Int
c = 42
10 changes: 10 additions & 0 deletions cabal-testsuite/PackageTests/ReplOptions/alt/alt.cabal
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
name: alt
version: 0.1
build-type: Simple
cabal-version: >= 1.10

library
exposed-modules: ModuleA, ModuleC
build-depends: base
default-language: Haskell2010

Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
# cabal clean
# cabal v2-repl
Error: [Cabal-7076]
Please pick a single [package:][ctype:]component (or all) as target for the REPL command. The packages in 'alt.project' from which to select a component target are:
- alt
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
# cabal clean
# cabal v2-repl
Error: [Cabal-7076]
Please pick a single [package:][ctype:]component (or all) as target for the REPL command. The packages in 'alt.project' from which to select a component target are:
- alt
23 changes: 20 additions & 3 deletions cabal-testsuite/PackageTests/ReplOptions/cabal.test.hs
Original file line number Diff line number Diff line change
@@ -1,29 +1,46 @@
import Test.Cabal.Prelude

singleOpts = ["--repl-options=-fwrite-interface"]
multiOpts = "--repl-options=-fdefer-typed-holes" : singleOpts
altProject = ("--project-file=alt.project" :)

main = do
cabalTest' "single-repl-options" $ do
cabal' "clean" []
res <- cabalWithStdin "v2-repl" ["--repl-options=-fwrite-interface"] ":set"
res <- cabalWithStdin "v2-repl" singleOpts ":set"
assertOutputContains "Ok, two modules loaded." res
assertOutputContains " -fwrite-interface" res

cabalTest' "alt-single-repl-options" $ do
cabal' "clean" []
-- We can't 'cabal repl' without a target when the project has a single package.
void $ fails $ cabalWithStdin "v2-repl" (altProject singleOpts) ":set"

cabalTest' "multiple-repl-options" $ do
cabal' "clean" []
res <- cabalWithStdin "v2-repl" ["--repl-options=-fwrite-interface", "--repl-options=-fdefer-typed-holes"] ":set"
res <- cabalWithStdin "v2-repl" multiOpts ":set"
assertOutputContains "Ok, two modules loaded." res
assertOutputContains " -fwrite-interface" res
assertOutputContains " -fdefer-typed-holes" res

cabalTest' "alt-multiple-repl-options" $ do
cabal' "clean" []
-- We can't 'cabal repl' without a target when the project has a single package.
void $ fails $ cabalWithStdin "v2-repl" (altProject multiOpts) ":set"

cabalTest' "single-repl-options-multiple-flags" $ do
cabal' "clean" []
res <- cabalWithStdin "v2-repl" ["--repl-options=-fdefer-typed-holes -fwrite-interface"] ":set"
assertOutputContains "Ok, two modules loaded." res
assertOutputContains " -fwrite-interface" res
assertOutputContains " -fdefer-typed-holes" res

cabalTest' "single-repl-options-multiple-flags-negative" $ do
cabal' "clean" []
res <- fails $ cabalWithStdin "v2-repl" ["--repl-options=-fwrite-interface -fdiagnostics-show-baret"] ":set"
assertOutputDoesNotContain "Ok, two modules loaded." res
assertOutputContains "unrecognised flag: -fdiagnostics-show-baret" res
assertOutputContains "did you mean one of:" res

cabalTest' "multiple-repl-options-multiple-flags" $ do
cabal' "clean" []
res <- cabalWithStdin "v2-repl" [
Expand Down
18 changes: 18 additions & 0 deletions cabal-testsuite/PackageTests/ReplProjectNoneTarget/cabal.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
# checking repl command with no project and --ignore-project
# cabal repl
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- fake-package-0 (interactive) (lib) (first run)
Configuring library for fake-package-0...
Warning: No exposed modules
# checking repl command with no project and no project options
# cabal repl
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- fake-package-0 (interactive) (lib) (configuration changed)
Configuring library for fake-package-0...
Warning: No exposed modules
# checking repl command with a missing project
# cabal repl
22 changes: 22 additions & 0 deletions cabal-testsuite/PackageTests/ReplProjectNoneTarget/cabal.test.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
import Test.Cabal.Prelude

main = cabalTest . recordMode RecordMarked $ do
let log = recordHeader . pure

-- The following output is not what we want but is the current behaviour that
-- refers to the fake package.
log "checking repl command with no project and --ignore-project"
ignored <- cabalWithStdin "repl" ["--ignore-project"] ""
assertOutputContains "fake-package-0 (interactive) (lib) (first run)" ignored

-- The following output is not what we want but is the current behaviour that
-- refers to the fake package.
log "checking repl command with no project and no project options"
noOptions <- cabalWithStdin "repl" [] ""
assertOutputContains "fake-package-0 (interactive) (lib) (configuration changed)" noOptions

log "checking repl command with a missing project"
missing <- fails $ cabalWithStdin "repl" [ "--project-file=missing.project" ] ""
assertOutputContains "The given project file 'missing.project' does not exist." missing

return ()
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
name: pkg-one
version: 0.1
license: BSD3
cabal-version: >= 1.2
build-type: Simple

library
exposed-modules: Foo
build-depends: base
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
name: pkg-one
version: 0.1
license: BSD3
cabal-version: >= 1.2
build-type: Simple

library
exposed-modules: Foo
build-depends: base
Loading
Loading