{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}

-- | cabal-install CLI command: run
--
module Distribution.Client.CmdRun (
    -- * The @run@ CLI and action
    runCommand,
    runAction,
    handleShebang, validScript,

    -- * Internals exposed for testing
    matchesMultipleProblem,
    noExesProblem,
    selectPackageTargets,
    selectComponentTarget
  ) where

import Prelude ()
import Distribution.Client.Compat.Prelude hiding (toList)

import Distribution.Client.CmdErrorMessages
         ( renderTargetSelector, showTargetSelector,
           renderTargetProblem,
           renderTargetProblemNoTargets, plural, targetSelectorPluralPkgs,
           targetSelectorFilter, renderListCommaAnd,
           renderListPretty )
import Distribution.Client.GlobalFlags
         ( defaultGlobalFlags )
import Distribution.Client.InstallPlan
         ( toList, foldPlanPackage )
import Distribution.Client.NixStyleOptions
         ( NixStyleFlags (..), nixStyleOptions, defaultNixStyleFlags )
import Distribution.Client.ProjectOrchestration
import Distribution.Client.ProjectPlanning
         ( ElaboratedConfiguredPackage(..)
         , ElaboratedInstallPlan, binDirectoryFor )
import Distribution.Client.ProjectPlanning.Types
         ( dataDirsEnvironmentForPlan )
import Distribution.Client.ScriptUtils
         ( AcceptNoTargets(..), TargetContext(..)
         , updateContextAndWriteProjectFile, withContextAndSelectors
         , movedExePath )
import Distribution.Client.Setup
         ( GlobalFlags(..), ConfigFlags(..) )
import Distribution.Client.TargetProblem
         ( TargetProblem (..) )
import Distribution.Simple.Command
         ( CommandUI(..), usageAlternatives )
import Distribution.Simple.Flag
         ( fromFlagOrDefault )
import Distribution.Simple.Program.Run
         ( runProgramInvocation, ProgramInvocation(..),
           emptyProgramInvocation )
import Distribution.Simple.Utils
         ( wrapText, die', info, notice, safeHead )
import Distribution.Types.ComponentName
         ( componentNameRaw )
import Distribution.Types.UnitId
         ( UnitId )

import Distribution.Types.UnqualComponentName
         ( UnqualComponentName, unUnqualComponentName )
import Distribution.Verbosity
         ( normal, silent )

import Data.List (group)
import qualified Data.Set as Set
import System.Directory
         ( doesFileExist )
import System.FilePath
         ( (</>), isValid, isPathSeparator )

runCommand :: CommandUI (NixStyleFlags ())
runCommand :: CommandUI (NixStyleFlags ())
runCommand = CommandUI
  { commandName :: [Char]
commandName         = [Char]
"v2-run"
  , commandSynopsis :: [Char]
commandSynopsis     = [Char]
"Run an executable."
  , commandUsage :: [Char] -> [Char]
commandUsage        = [Char] -> [[Char]] -> [Char] -> [Char]
usageAlternatives [Char]
"v2-run"
                          [ [Char]
"[TARGET] [FLAGS] [-- EXECUTABLE_FLAGS]" ]
  , commandDescription :: Maybe ([Char] -> [Char])
commandDescription  = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \[Char]
pname -> [Char] -> [Char]
wrapText forall a b. (a -> b) -> a -> b
$
         [Char]
"Runs the specified executable-like component (an executable, a test, "
      forall a. [a] -> [a] -> [a]
++ [Char]
"or a benchmark), first ensuring it is up to date.\n\n"

      forall a. [a] -> [a] -> [a]
++ [Char]
"Any executable-like component in any package in the project can be "
      forall a. [a] -> [a] -> [a]
++ [Char]
"specified. A package can be specified if contains just one "
      forall a. [a] -> [a] -> [a]
++ [Char]
"executable-like, preferring a single executable. The default is to "
      forall a. [a] -> [a] -> [a]
++ [Char]
"use the package in the current directory if it contains just one "
      forall a. [a] -> [a] -> [a]
++ [Char]
"executable-like.\n\n"

      forall a. [a] -> [a] -> [a]
++ [Char]
"Extra arguments can be passed to the program, but use '--' to "
      forall a. [a] -> [a] -> [a]
++ [Char]
"separate arguments for the program from arguments for " forall a. [a] -> [a] -> [a]
++ [Char]
pname
      forall a. [a] -> [a] -> [a]
++ [Char]
". The executable is run in an environment where it can find its "
      forall a. [a] -> [a] -> [a]
++ [Char]
"data files inplace in the build tree.\n\n"

      forall a. [a] -> [a] -> [a]
++ [Char]
"Dependencies are built or rebuilt as necessary. Additional "
      forall a. [a] -> [a] -> [a]
++ [Char]
"configuration flags can be specified on the command line and these "
      forall a. [a] -> [a] -> [a]
++ [Char]
"extend the project configuration from the 'cabal.project', "
      forall a. [a] -> [a] -> [a]
++ [Char]
"'cabal.project.local' and other files."
  , commandNotes :: Maybe ([Char] -> [Char])
commandNotes        = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \[Char]
pname ->
         [Char]
"Examples:\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"  " forall a. [a] -> [a] -> [a]
++ [Char]
pname forall a. [a] -> [a] -> [a]
++ [Char]
" v2-run\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"    Run the executable-like in the package in the current directory\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"  " forall a. [a] -> [a] -> [a]
++ [Char]
pname forall a. [a] -> [a] -> [a]
++ [Char]
" v2-run foo-tool\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"    Run the named executable-like (in any package in the project)\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"  " forall a. [a] -> [a] -> [a]
++ [Char]
pname forall a. [a] -> [a] -> [a]
++ [Char]
" v2-run pkgfoo:foo-tool\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"    Run the executable-like 'foo-tool' in the package 'pkgfoo'\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"  " forall a. [a] -> [a] -> [a]
++ [Char]
pname forall a. [a] -> [a] -> [a]
++ [Char]
" v2-run foo -O2 -- dothing --fooflag\n"
      forall a. [a] -> [a] -> [a]
++ [Char]
"    Build with '-O2' and run the program, passing it extra arguments.\n"

  , commandDefaultFlags :: NixStyleFlags ()
commandDefaultFlags = forall a. a -> NixStyleFlags a
defaultNixStyleFlags ()
  , commandOptions :: ShowOrParseArgs -> [OptionField (NixStyleFlags ())]
commandOptions      = forall a.
(ShowOrParseArgs -> [OptionField a])
-> ShowOrParseArgs -> [OptionField (NixStyleFlags a)]
nixStyleOptions (forall a b. a -> b -> a
const [])
  }

-- | The @run@ command runs a specified executable-like component, building it
-- first if necessary. The component can be either an executable, a test,
-- or a benchmark. This is particularly useful for passing arguments to
-- exes/tests/benchs by simply appending them after a @--@.
--
-- For more details on how this works, see the module
-- "Distribution.Client.ProjectOrchestration"
--
runAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
runAction :: NixStyleFlags () -> [[Char]] -> GlobalFlags -> IO ()
runAction flags :: NixStyleFlags ()
flags@NixStyleFlags {()
ConfigFlags
HaddockFlags
TestFlags
BenchmarkFlags
ProjectFlags
InstallFlags
ConfigExFlags
extraFlags :: forall a. NixStyleFlags a -> a
projectFlags :: forall a. NixStyleFlags a -> ProjectFlags
benchmarkFlags :: forall a. NixStyleFlags a -> BenchmarkFlags
testFlags :: forall a. NixStyleFlags a -> TestFlags
haddockFlags :: forall a. NixStyleFlags a -> HaddockFlags
installFlags :: forall a. NixStyleFlags a -> InstallFlags
configExFlags :: forall a. NixStyleFlags a -> ConfigExFlags
configFlags :: forall a. NixStyleFlags a -> ConfigFlags
extraFlags :: ()
projectFlags :: ProjectFlags
benchmarkFlags :: BenchmarkFlags
testFlags :: TestFlags
haddockFlags :: HaddockFlags
installFlags :: InstallFlags
configExFlags :: ConfigExFlags
configFlags :: ConfigFlags
..} [[Char]]
targetAndArgs GlobalFlags
globalFlags
  = forall a b.
AcceptNoTargets
-> Maybe ComponentKind
-> NixStyleFlags a
-> [[Char]]
-> GlobalFlags
-> CurrentCommand
-> (TargetContext
    -> ProjectBaseContext -> [TargetSelector] -> IO b)
-> IO b
withContextAndSelectors AcceptNoTargets
RejectNoTargets (forall a. a -> Maybe a
Just ComponentKind
ExeKind) NixStyleFlags ()
flags [[Char]]
targetStr GlobalFlags
globalFlags CurrentCommand
OtherCommand forall a b. (a -> b) -> a -> b
$ \TargetContext
targetCtx ProjectBaseContext
ctx [TargetSelector]
targetSelectors -> do
    (ProjectBaseContext
baseCtx, Verbosity
defaultVerbosity) <- case TargetContext
targetCtx of
      TargetContext
ProjectContext             -> forall (m :: * -> *) a. Monad m => a -> m a
return (ProjectBaseContext
ctx, Verbosity
normal)
      TargetContext
GlobalContext              -> forall (m :: * -> *) a. Monad m => a -> m a
return (ProjectBaseContext
ctx, Verbosity
normal)
      ScriptContext [Char]
path Executable
exemeta -> (, Verbosity
silent) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProjectBaseContext -> [Char] -> Executable -> IO ProjectBaseContext
updateContextAndWriteProjectFile ProjectBaseContext
ctx [Char]
path Executable
exemeta

    let verbosity :: Verbosity
verbosity = forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
defaultVerbosity (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
configFlags)

    ProjectBuildContext
buildCtx <-
      Verbosity
-> ProjectBaseContext
-> (ElaboratedInstallPlan
    -> IO (ElaboratedInstallPlan, TargetsMap))
-> IO ProjectBuildContext
runProjectPreBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx forall a b. (a -> b) -> a -> b
$ \ElaboratedInstallPlan
elaboratedPlan -> do

            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (BuildTimeSettings -> Bool
buildSettingOnlyDeps (ProjectBaseContext -> BuildTimeSettings
buildSettings ProjectBaseContext
baseCtx)) forall a b. (a -> b) -> a -> b
$
              forall a. Verbosity -> [Char] -> IO a
die' Verbosity
verbosity forall a b. (a -> b) -> a -> b
$
                  [Char]
"The run command does not support '--only-dependencies'. "
               forall a. [a] -> [a] -> [a]
++ [Char]
"You may wish to use 'build --only-dependencies' and then "
               forall a. [a] -> [a] -> [a]
++ [Char]
"use 'run'."

            -- Interpret the targets on the command line as build targets
            -- (as opposed to say repl or haddock targets).
            TargetsMap
targets <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. Verbosity -> [RunTargetProblem] -> IO a
reportTargetProblems Verbosity
verbosity) forall (m :: * -> *) a. Monad m => a -> m a
return
                     forall a b. (a -> b) -> a -> b
$ forall err.
(forall k.
 TargetSelector
 -> [AvailableTarget k] -> Either (TargetProblem err) [k])
-> (forall k.
    SubComponentTarget
    -> AvailableTarget k -> Either (TargetProblem err) k)
-> ElaboratedInstallPlan
-> Maybe SourcePackageDb
-> [TargetSelector]
-> Either [TargetProblem err] TargetsMap
resolveTargets
                         forall k.
TargetSelector
-> [AvailableTarget k] -> Either RunTargetProblem [k]
selectPackageTargets
                         forall k.
SubComponentTarget
-> AvailableTarget k -> Either RunTargetProblem k
selectComponentTarget
                         ElaboratedInstallPlan
elaboratedPlan
                         forall a. Maybe a
Nothing
                         [TargetSelector]
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.
            --
            -- Note that we discard the target and return the whole 'TargetsMap',
            -- so this check will be repeated (and must succeed) after
            -- the 'runProjectPreBuildPhase'. Keep it in mind when modifying this.
            (UnitId, UnqualComponentName)
_ <- IO (UnitId, UnqualComponentName)
-> TargetsMap -> IO (UnitId, UnqualComponentName)
singleExeOrElse
                   (forall a. Verbosity -> [RunTargetProblem] -> IO a
reportTargetProblems
                      Verbosity
verbosity
                      [TargetsMap -> RunTargetProblem
multipleTargetsProblem TargetsMap
targets])
                   TargetsMap
targets

            let elaboratedPlan' :: ElaboratedInstallPlan
elaboratedPlan' = TargetAction
-> TargetsMap -> ElaboratedInstallPlan -> ElaboratedInstallPlan
pruneInstallPlanToTargets
                                    TargetAction
TargetActionBuild
                                    TargetsMap
targets
                                    ElaboratedInstallPlan
elaboratedPlan
            forall (m :: * -> *) a. Monad m => a -> m a
return (ElaboratedInstallPlan
elaboratedPlan', TargetsMap
targets)

    (UnitId
selectedUnitId, UnqualComponentName
selectedComponent) <-
      -- Slight duplication with 'runProjectPreBuildPhase'.
      IO (UnitId, UnqualComponentName)
-> TargetsMap -> IO (UnitId, UnqualComponentName)
singleExeOrElse
        (forall a. Verbosity -> [Char] -> IO a
die' Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ [Char]
"No or multiple targets given, but the run "
                       forall a. [a] -> [a] -> [a]
++ [Char]
"phase has been reached. This is a bug.")
        forall a b. (a -> b) -> a -> b
$ ProjectBuildContext -> TargetsMap
targetsMap ProjectBuildContext
buildCtx

    Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO ()
printPlan Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx

    BuildOutcomes
buildOutcomes <- Verbosity
-> ProjectBaseContext -> ProjectBuildContext -> IO BuildOutcomes
runProjectBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx
    Verbosity
-> ProjectBaseContext
-> ProjectBuildContext
-> BuildOutcomes
-> IO ()
runProjectPostBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx BuildOutcomes
buildOutcomes


    let elaboratedPlan :: ElaboratedInstallPlan
elaboratedPlan = ProjectBuildContext -> ElaboratedInstallPlan
elaboratedPlanToExecute ProjectBuildContext
buildCtx
        matchingElaboratedConfiguredPackages :: [ElaboratedConfiguredPackage]
matchingElaboratedConfiguredPackages =
          UnitId -> ElaboratedInstallPlan -> [ElaboratedConfiguredPackage]
matchingPackagesByUnitId
            UnitId
selectedUnitId
            ElaboratedInstallPlan
elaboratedPlan

    let exeName :: [Char]
exeName = UnqualComponentName -> [Char]
unUnqualComponentName UnqualComponentName
selectedComponent

    -- In the common case, we expect @matchingElaboratedConfiguredPackages@
    -- to consist of a single element that provides a single way of building
    -- an appropriately-named executable. In that case we take that
    -- package and continue.
    --
    -- However, multiple packages/components could provide that
    -- executable, or it's possible we don't find the executable anywhere
    -- in the build plan. I suppose in principle it's also possible that
    -- a single package provides an executable in two different ways,
    -- though that's probably a bug if. Anyway it's a good lint to report
    -- an error in all of these cases, even if some seem like they
    -- shouldn't happen.
    ElaboratedConfiguredPackage
pkg <- case [ElaboratedConfiguredPackage]
matchingElaboratedConfiguredPackages of
      [] -> forall a. Verbosity -> [Char] -> IO a
die' Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ [Char]
"Unknown executable "
                          forall a. [a] -> [a] -> [a]
++ [Char]
exeName
                          forall a. [a] -> [a] -> [a]
++ [Char]
" in package "
                          forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> [Char]
prettyShow UnitId
selectedUnitId
      [ElaboratedConfiguredPackage
elabPkg] -> do
        Verbosity -> [Char] -> IO ()
info Verbosity
verbosity forall a b. (a -> b) -> a -> b
$ [Char]
"Selecting "
                       forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> [Char]
prettyShow UnitId
selectedUnitId
                       forall a. [a] -> [a] -> [a]
++ [Char]
" to supply " forall a. [a] -> [a] -> [a]
++ [Char]
exeName
        forall (m :: * -> *) a. Monad m => a -> m a
return ElaboratedConfiguredPackage
elabPkg
      [ElaboratedConfiguredPackage]
elabPkgs -> forall a. Verbosity -> [Char] -> IO a
die' Verbosity
verbosity
        forall a b. (a -> b) -> a -> b
$ [Char]
"Multiple matching executables found matching "
        forall a. [a] -> [a] -> [a]
++ [Char]
exeName
        forall a. [a] -> [a] -> [a]
++ [Char]
":\n"
        forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unlines (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ElaboratedConfiguredPackage
p -> [Char]
" - in package " forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> [Char]
prettyShow (ElaboratedConfiguredPackage -> UnitId
elabUnitId ElaboratedConfiguredPackage
p)) [ElaboratedConfiguredPackage]
elabPkgs)

    let defaultExePath :: [Char]
defaultExePath = DistDirLayout
-> ElaboratedSharedConfig
-> ElaboratedConfiguredPackage
-> [Char]
-> [Char]
binDirectoryFor
                            (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx)
                            (ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx)
                             ElaboratedConfiguredPackage
pkg
                             [Char]
exeName
                       [Char] -> [Char] -> [Char]
</> [Char]
exeName
        exePath :: [Char]
exePath = forall a. a -> Maybe a -> a
fromMaybe [Char]
defaultExePath (UnqualComponentName
-> DistDirLayout
-> ElaboratedSharedConfig
-> ElaboratedConfiguredPackage
-> Maybe [Char]
movedExePath UnqualComponentName
selectedComponent (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx) (ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx) ElaboratedConfiguredPackage
pkg)

    let dryRun :: Bool
dryRun = BuildTimeSettings -> Bool
buildSettingDryRun (ProjectBaseContext -> BuildTimeSettings
buildSettings ProjectBaseContext
baseCtx)
              Bool -> Bool -> Bool
|| BuildTimeSettings -> Bool
buildSettingOnlyDownload (ProjectBaseContext -> BuildTimeSettings
buildSettings ProjectBaseContext
baseCtx)

    if Bool
dryRun
       then Verbosity -> [Char] -> IO ()
notice Verbosity
verbosity [Char]
"Running of executable suppressed by flag(s)"
       else
         Verbosity -> ProgramInvocation -> IO ()
runProgramInvocation
           Verbosity
verbosity
           ProgramInvocation
emptyProgramInvocation {
             progInvokePath :: [Char]
progInvokePath  = [Char]
exePath,
             progInvokeArgs :: [[Char]]
progInvokeArgs  = [[Char]]
args,
             progInvokeEnv :: [([Char], Maybe [Char])]
progInvokeEnv   = DistDirLayout -> ElaboratedInstallPlan -> [([Char], Maybe [Char])]
dataDirsEnvironmentForPlan
                                 (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx)
                                 ElaboratedInstallPlan
elaboratedPlan
           }
  where
    ([[Char]]
targetStr, [[Char]]
args) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [[Char]]
targetAndArgs

-- | Used by the main CLI parser as heuristic to decide whether @cabal@ was
-- invoked as a script interpreter, i.e. via
--
-- > #! /usr/bin/env cabal
--
-- or
--
-- > #! /usr/bin/cabal
--
-- As the first argument passed to `cabal` will be a filepath to the
-- script to be interpreted.
--
-- See also 'handleShebang'
validScript :: String -> IO Bool
validScript :: [Char] -> IO Bool
validScript [Char]
script
  | [Char] -> Bool
isValid [Char]
script Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isPathSeparator [Char]
script = [Char] -> IO Bool
doesFileExist [Char]
script
  | Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False

-- | Handle @cabal@ invoked as script interpreter, see also 'validScript'
--
-- First argument is the 'FilePath' to the script to be executed; second
-- argument is a list of arguments to be passed to the script.
handleShebang :: FilePath -> [String] -> IO ()
handleShebang :: [Char] -> [[Char]] -> IO ()
handleShebang [Char]
script [[Char]]
args =
  NixStyleFlags () -> [[Char]] -> GlobalFlags -> IO ()
runAction (forall flags. CommandUI flags -> flags
commandDefaultFlags CommandUI (NixStyleFlags ())
runCommand) ([Char]
scriptforall a. a -> [a] -> [a]
:[[Char]]
args) GlobalFlags
defaultGlobalFlags

singleExeOrElse :: IO (UnitId, UnqualComponentName) -> TargetsMap -> IO (UnitId, UnqualComponentName)
singleExeOrElse :: IO (UnitId, UnqualComponentName)
-> TargetsMap -> IO (UnitId, UnqualComponentName)
singleExeOrElse IO (UnitId, UnqualComponentName)
action TargetsMap
targetsMap =
  case forall a. Set a -> [a]
Set.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. TargetsMap -> Set (UnitId, ComponentName)
distinctTargetComponents forall a b. (a -> b) -> a -> b
$ TargetsMap
targetsMap
  of [(UnitId
unitId, CExeName UnqualComponentName
component)] -> forall (m :: * -> *) a. Monad m => a -> m a
return (UnitId
unitId, UnqualComponentName
component)
     [(UnitId
unitId, CTestName UnqualComponentName
component)] -> forall (m :: * -> *) a. Monad m => a -> m a
return (UnitId
unitId, UnqualComponentName
component)
     [(UnitId
unitId, CBenchName UnqualComponentName
component)] -> forall (m :: * -> *) a. Monad m => a -> m a
return (UnitId
unitId, UnqualComponentName
component)
     [(UnitId, ComponentName)]
_   -> IO (UnitId, UnqualComponentName)
action

-- | Filter the 'ElaboratedInstallPlan' keeping only the
-- 'ElaboratedConfiguredPackage's that match the specified
-- 'UnitId'.
matchingPackagesByUnitId :: UnitId
                         -> ElaboratedInstallPlan
                         -> [ElaboratedConfiguredPackage]
matchingPackagesByUnitId :: UnitId -> ElaboratedInstallPlan -> [ElaboratedConfiguredPackage]
matchingPackagesByUnitId UnitId
uid =
          forall a. [Maybe a] -> [a]
catMaybes
          forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall ipkg a srcpkg.
(ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a
foldPlanPackage
                    (forall a b. a -> b -> a
const forall a. Maybe a
Nothing)
                    (\ElaboratedConfiguredPackage
x -> if ElaboratedConfiguredPackage -> UnitId
elabUnitId ElaboratedConfiguredPackage
x forall a. Eq a => a -> a -> Bool
== UnitId
uid
                           then forall a. a -> Maybe a
Just ElaboratedConfiguredPackage
x
                           else forall a. Maybe a
Nothing))
          forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ipkg srcpkg.
GenericInstallPlan ipkg srcpkg -> [GenericPlanPackage ipkg srcpkg]
toList

-- | This defines what a 'TargetSelector' means for the @run@ command.
-- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
-- or otherwise classifies the problem.
--
-- For the @run@ command we select the exe if there is only one and it's
-- buildable. Fail if there are no or multiple buildable exe components.
--
selectPackageTargets :: TargetSelector
                     -> [AvailableTarget k] -> Either RunTargetProblem [k]
selectPackageTargets :: forall k.
TargetSelector
-> [AvailableTarget k] -> Either RunTargetProblem [k]
selectPackageTargets TargetSelector
targetSelector [AvailableTarget k]
targets

  -- If there is a single executable component, select that. See #7403
  | [k
target] <- [k]
targetsExesBuildable
  = forall a b. b -> Either a b
Right [k
target]

  -- Otherwise, if there is a single executable-like component left, select that.
  | [k
target] <- [k]
targetsExeLikesBuildable
  = forall a b. b -> Either a b
Right [k
target]

  -- but fail if there are multiple buildable executables.
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [k]
targetsExeLikesBuildable)
  = forall a b. a -> Either a b
Left (TargetSelector -> [AvailableTarget ()] -> RunTargetProblem
matchesMultipleProblem TargetSelector
targetSelector [AvailableTarget ()]
targetsExeLikesBuildable')

    -- If there are executables but none are buildable then we report those
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AvailableTarget ()]
targetsExeLikes')
  = forall a b. a -> Either a b
Left (forall a. TargetSelector -> [AvailableTarget ()] -> TargetProblem a
TargetProblemNoneEnabled TargetSelector
targetSelector [AvailableTarget ()]
targetsExeLikes')

    -- If there are no executables but some other targets then we report that
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AvailableTarget k]
targets)
  = forall a b. a -> Either a b
Left (TargetSelector -> RunTargetProblem
noExesProblem TargetSelector
targetSelector)

    -- If there are no targets at all then we report that
  | Bool
otherwise
  = forall a b. a -> Either a b
Left (forall a. TargetSelector -> TargetProblem a
TargetProblemNoTargets TargetSelector
targetSelector)
  where
    -- Targets that are precisely executables
    targetsExes :: [AvailableTarget k]
targetsExes = forall k.
ComponentKind -> [AvailableTarget k] -> [AvailableTarget k]
filterTargetsKind ComponentKind
ExeKind [AvailableTarget k]
targets
    targetsExesBuildable :: [k]
targetsExesBuildable = forall k. [AvailableTarget k] -> [k]
selectBuildableTargets [AvailableTarget k]
targetsExes

    -- Any target that could be executed
    targetsExeLikes :: [AvailableTarget k]
targetsExeLikes = [AvailableTarget k]
targetsExes
                   forall a. [a] -> [a] -> [a]
++ forall k.
ComponentKind -> [AvailableTarget k] -> [AvailableTarget k]
filterTargetsKind ComponentKind
TestKind [AvailableTarget k]
targets
                   forall a. [a] -> [a] -> [a]
++ forall k.
ComponentKind -> [AvailableTarget k] -> [AvailableTarget k]
filterTargetsKind ComponentKind
BenchKind [AvailableTarget k]
targets

    ([k]
targetsExeLikesBuildable,
     [AvailableTarget ()]
targetsExeLikesBuildable') = forall k. [AvailableTarget k] -> ([k], [AvailableTarget ()])
selectBuildableTargets' [AvailableTarget k]
targetsExeLikes

    targetsExeLikes' :: [AvailableTarget ()]
targetsExeLikes'             = forall k. [AvailableTarget k] -> [AvailableTarget ()]
forgetTargetsDetail [AvailableTarget k]
targetsExeLikes


-- | For a 'TargetComponent' 'TargetSelector', check if the component can be
-- selected.
--
-- For the @run@ command we just need to check it is a executable-like
-- (an executable, a test, or a benchmark), in addition
-- to the basic checks on being buildable etc.
--
selectComponentTarget :: SubComponentTarget
                      -> AvailableTarget k -> Either RunTargetProblem  k
selectComponentTarget :: forall k.
SubComponentTarget
-> AvailableTarget k -> Either RunTargetProblem k
selectComponentTarget subtarget :: SubComponentTarget
subtarget@SubComponentTarget
WholeComponent AvailableTarget k
t
  = case forall k. AvailableTarget k -> ComponentName
availableTargetComponentName AvailableTarget k
t
    of CExeName UnqualComponentName
_ -> forall {a}. Either (TargetProblem a) k
component
       CTestName UnqualComponentName
_ -> forall {a}. Either (TargetProblem a) k
component
       CBenchName UnqualComponentName
_ -> forall {a}. Either (TargetProblem a) k
component
       ComponentName
_ -> forall a b. a -> Either a b
Left (PackageId -> ComponentName -> RunTargetProblem
componentNotExeProblem PackageId
pkgid ComponentName
cname)
    where pkgid :: PackageId
pkgid = forall k. AvailableTarget k -> PackageId
availableTargetPackageId AvailableTarget k
t
          cname :: ComponentName
cname = forall k. AvailableTarget k -> ComponentName
availableTargetComponentName AvailableTarget k
t
          component :: Either (TargetProblem a) k
component = forall k a.
SubComponentTarget
-> AvailableTarget k -> Either (TargetProblem a) k
selectComponentTargetBasic SubComponentTarget
subtarget AvailableTarget k
t

selectComponentTarget SubComponentTarget
subtarget AvailableTarget k
t
  = forall a b. a -> Either a b
Left (PackageId
-> ComponentName -> SubComponentTarget -> RunTargetProblem
isSubComponentProblem (forall k. AvailableTarget k -> PackageId
availableTargetPackageId AvailableTarget k
t)
           (forall k. AvailableTarget k -> ComponentName
availableTargetComponentName AvailableTarget k
t)
           SubComponentTarget
subtarget)

-- | The various error conditions that can occur when matching a
-- 'TargetSelector' against 'AvailableTarget's for the @run@ command.
--
data RunProblem =
     -- | The 'TargetSelector' matches targets but no executables
     TargetProblemNoExes      TargetSelector

     -- | A single 'TargetSelector' matches multiple targets
   | TargetProblemMatchesMultiple TargetSelector [AvailableTarget ()]

     -- | Multiple 'TargetSelector's match multiple targets
   | TargetProblemMultipleTargets TargetsMap

     -- | The 'TargetSelector' refers to a component that is not an executable
   | TargetProblemComponentNotExe PackageId ComponentName

     -- | Asking to run an individual file or module is not supported
   | TargetProblemIsSubComponent  PackageId ComponentName SubComponentTarget
  deriving (RunProblem -> RunProblem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RunProblem -> RunProblem -> Bool
$c/= :: RunProblem -> RunProblem -> Bool
== :: RunProblem -> RunProblem -> Bool
$c== :: RunProblem -> RunProblem -> Bool
Eq, Int -> RunProblem -> [Char] -> [Char]
[RunProblem] -> [Char] -> [Char]
RunProblem -> [Char]
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [RunProblem] -> [Char] -> [Char]
$cshowList :: [RunProblem] -> [Char] -> [Char]
show :: RunProblem -> [Char]
$cshow :: RunProblem -> [Char]
showsPrec :: Int -> RunProblem -> [Char] -> [Char]
$cshowsPrec :: Int -> RunProblem -> [Char] -> [Char]
Show)

type RunTargetProblem = TargetProblem RunProblem

noExesProblem :: TargetSelector -> RunTargetProblem
noExesProblem :: TargetSelector -> RunTargetProblem
noExesProblem = forall a. a -> TargetProblem a
CustomTargetProblem forall b c a. (b -> c) -> (a -> b) -> a -> c
. TargetSelector -> RunProblem
TargetProblemNoExes

matchesMultipleProblem :: TargetSelector -> [AvailableTarget ()] -> RunTargetProblem
matchesMultipleProblem :: TargetSelector -> [AvailableTarget ()] -> RunTargetProblem
matchesMultipleProblem TargetSelector
selector [AvailableTarget ()]
targets = forall a. a -> TargetProblem a
CustomTargetProblem forall a b. (a -> b) -> a -> b
$
    TargetSelector -> [AvailableTarget ()] -> RunProblem
TargetProblemMatchesMultiple TargetSelector
selector [AvailableTarget ()]
targets

multipleTargetsProblem :: TargetsMap -> TargetProblem RunProblem
multipleTargetsProblem :: TargetsMap -> RunTargetProblem
multipleTargetsProblem = forall a. a -> TargetProblem a
CustomTargetProblem forall b c a. (b -> c) -> (a -> b) -> a -> c
. TargetsMap -> RunProblem
TargetProblemMultipleTargets

componentNotExeProblem :: PackageId -> ComponentName -> TargetProblem RunProblem
componentNotExeProblem :: PackageId -> ComponentName -> RunTargetProblem
componentNotExeProblem PackageId
pkgid ComponentName
name = forall a. a -> TargetProblem a
CustomTargetProblem forall a b. (a -> b) -> a -> b
$
    PackageId -> ComponentName -> RunProblem
TargetProblemComponentNotExe PackageId
pkgid ComponentName
name

isSubComponentProblem
  :: PackageId
  -> ComponentName
  -> SubComponentTarget
  -> TargetProblem RunProblem
isSubComponentProblem :: PackageId
-> ComponentName -> SubComponentTarget -> RunTargetProblem
isSubComponentProblem PackageId
pkgid ComponentName
name SubComponentTarget
subcomponent = forall a. a -> TargetProblem a
CustomTargetProblem forall a b. (a -> b) -> a -> b
$
    PackageId -> ComponentName -> SubComponentTarget -> RunProblem
TargetProblemIsSubComponent PackageId
pkgid ComponentName
name SubComponentTarget
subcomponent

reportTargetProblems :: Verbosity -> [RunTargetProblem] -> IO a
reportTargetProblems :: forall a. Verbosity -> [RunTargetProblem] -> IO a
reportTargetProblems Verbosity
verbosity =
    forall a. Verbosity -> [Char] -> IO a
die' Verbosity
verbosity forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [Char]
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map RunTargetProblem -> [Char]
renderRunTargetProblem

renderRunTargetProblem :: RunTargetProblem -> String
renderRunTargetProblem :: RunTargetProblem -> [Char]
renderRunTargetProblem (TargetProblemNoTargets TargetSelector
targetSelector) =
    case TargetSelector -> Maybe ComponentKind
targetSelectorFilter TargetSelector
targetSelector of
      Just ComponentKind
kind | ComponentKind
kind forall a. Eq a => a -> a -> Bool
/= ComponentKind
ExeKind
        -> [Char]
"The run command is for running executables, but the target '"
           forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
showTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
"' refers to "
           forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
renderTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
"."

      Maybe ComponentKind
_ -> [Char] -> TargetSelector -> [Char]
renderTargetProblemNoTargets [Char]
"run" TargetSelector
targetSelector
renderRunTargetProblem RunTargetProblem
problem =
    forall a. [Char] -> (a -> [Char]) -> TargetProblem a -> [Char]
renderTargetProblem [Char]
"run" RunProblem -> [Char]
renderRunProblem RunTargetProblem
problem

renderRunProblem :: RunProblem -> String
renderRunProblem :: RunProblem -> [Char]
renderRunProblem (TargetProblemMatchesMultiple TargetSelector
targetSelector [AvailableTarget ()]
targets) =
    [Char]
"The run command is for running a single executable at once. The target '"
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
showTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
"' refers to "
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
renderTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
" which includes \n"
 forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unlines ((\([Char]
label, [[Char]]
xs) -> [Char]
"- " forall a. [a] -> [a] -> [a]
++ [Char]
label forall a. [a] -> [a] -> [a]
++ [Char]
": " forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
renderListPretty [[Char]]
xs)
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b. [a] -> [b] -> [(a, b)]
zip [[Char]
"executables", [Char]
"test-suites", [Char]
"benchmarks"]
     forall a b. (a -> b) -> a -> b
$  forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map [[Char]] -> [[Char]]
removeDuplicates
     forall a b. (a -> b) -> a -> b
$  forall a b. (a -> b) -> [a] -> [b]
map (ComponentName -> [Char]
componentNameRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k. AvailableTarget k -> ComponentName
availableTargetComponentName)
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall k.
ComponentKind -> [AvailableTarget k] -> [AvailableTarget k]
filterTargetsKind forall a b. (a -> b) -> a -> b
$ [AvailableTarget ()]
targets) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ComponentKind
ExeKind, ComponentKind
TestKind, ComponentKind
BenchKind] ))
    where removeDuplicates :: [[Char]] -> [[Char]]
removeDuplicates = forall a. [Maybe a] -> [a]
catMaybes forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> Maybe a
safeHead forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => [a] -> [[a]]
group forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
sort

renderRunProblem (TargetProblemMultipleTargets TargetsMap
selectorMap) =
    [Char]
"The run command is for running a single executable at once. The targets "
 forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
renderListCommaAnd [ [Char]
"'" forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
showTargetSelector TargetSelector
ts forall a. [a] -> [a] -> [a]
++ [Char]
"'"
                       | TargetSelector
ts <- TargetsMap -> [TargetSelector]
uniqueTargetSelectors TargetsMap
selectorMap ]
 forall a. [a] -> [a] -> [a]
++ [Char]
" refer to different executables."

renderRunProblem (TargetProblemComponentNotExe PackageId
pkgid ComponentName
cname) =
    [Char]
"The run command is for running executables, but the target '"
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
showTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
"' refers to "
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
renderTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
" from the package "
 forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> [Char]
prettyShow PackageId
pkgid forall a. [a] -> [a] -> [a]
++ [Char]
"."
  where
    targetSelector :: TargetSelector
targetSelector = PackageId -> ComponentName -> SubComponentTarget -> TargetSelector
TargetComponent PackageId
pkgid ComponentName
cname SubComponentTarget
WholeComponent

renderRunProblem (TargetProblemIsSubComponent PackageId
pkgid ComponentName
cname SubComponentTarget
subtarget) =
    [Char]
"The run command can only run an executable as a whole, "
 forall a. [a] -> [a] -> [a]
++ [Char]
"not files or modules within them, but the target '"
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
showTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
"' refers to "
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
renderTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ [Char]
"."
  where
    targetSelector :: TargetSelector
targetSelector = PackageId -> ComponentName -> SubComponentTarget -> TargetSelector
TargetComponent PackageId
pkgid ComponentName
cname SubComponentTarget
subtarget

renderRunProblem (TargetProblemNoExes TargetSelector
targetSelector) =
    [Char]
"Cannot run the target '" forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
showTargetSelector TargetSelector
targetSelector
 forall a. [a] -> [a] -> [a]
++ [Char]
"' which refers to " forall a. [a] -> [a] -> [a]
++ TargetSelector -> [Char]
renderTargetSelector TargetSelector
targetSelector
 forall a. [a] -> [a] -> [a]
++ [Char]
" because "
 forall a. [a] -> [a] -> [a]
++ forall a. Plural -> a -> a -> a
plural (TargetSelector -> Plural
targetSelectorPluralPkgs TargetSelector
targetSelector) [Char]
"it does" [Char]
"they do"
 forall a. [a] -> [a] -> [a]
++ [Char]
" not contain any executables."