-------------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Client.Exec
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- Implementation of the 'v2-exec' command for running an arbitrary executable
-- in an environment suited to the part of the store built for a project.
-------------------------------------------------------------------------------

{-# LANGUAGE RecordWildCards #-}
module Distribution.Client.CmdExec
  ( execAction
  , execCommand
  ) where

import Distribution.Client.DistDirLayout
  ( DistDirLayout(..)
  )
import Distribution.Client.InstallPlan
  ( GenericPlanPackage(..)
  , toGraph
  )
import Distribution.Client.NixStyleOptions
         ( NixStyleFlags (..), nixStyleOptions, defaultNixStyleFlags )
import Distribution.Client.Setup
  ( ConfigFlags(configVerbosity)
  , GlobalFlags
  )
import Distribution.Client.ProjectFlags
  ( removeIgnoreProjectOption
  )
import Distribution.Client.ProjectOrchestration
  ( ProjectBuildContext(..)
  , runProjectPreBuildPhase
  , CurrentCommand(..)
  , establishProjectBaseContext
  , distDirLayout
  , commandLineFlagsToProjectConfig
  , ProjectBaseContext(..)
  , BuildTimeSettings(..)
  )
import Distribution.Client.ProjectPlanOutput
  ( updatePostBuildProjectStatus
  , createPackageEnvironment
  , argsEquivalentOfGhcEnvironmentFile
  , PostBuildProjectStatus
  )
import qualified Distribution.Client.ProjectPlanning as Planning
import Distribution.Client.ProjectPlanning
  ( ElaboratedInstallPlan
  , ElaboratedSharedConfig(..)
  )
import Distribution.Simple.Command
  ( CommandUI(..) )
import Distribution.Simple.Program.Db
  ( modifyProgramSearchPath
  , requireProgram
  , configuredPrograms
  )
import Distribution.Simple.Program.Find
  ( ProgramSearchPathEntry(..)
  )
import Distribution.Simple.Program.Run
  ( programInvocation
  , runProgramInvocation
  )
import Distribution.Simple.Program.Types
  ( programOverrideEnv
  , programDefaultArgs
  , programPath
  , simpleProgram
  , ConfiguredProgram
  )
import Distribution.Simple.GHC
  ( getImplInfo
  , GhcImplInfo(supportsPkgEnvFiles) )
import Distribution.Simple.Flag
  ( fromFlagOrDefault
  )
import Distribution.Simple.Utils
  ( die'
  , info
  , createDirectoryIfMissingVerbose
  , withTempDirectory
  , wrapText
  , notice
  )
import Distribution.Verbosity
  ( normal
  )

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

import qualified Data.Set as S
import qualified Data.Map as M

execCommand :: CommandUI (NixStyleFlags ())
execCommand :: CommandUI (NixStyleFlags ())
execCommand = CommandUI
  { commandName :: FilePath
commandName = FilePath
"v2-exec"
  , commandSynopsis :: FilePath
commandSynopsis = FilePath
"Give a command access to the store."
  , commandUsage :: FilePath -> FilePath
commandUsage = \FilePath
pname ->
    FilePath
"Usage: " forall a. [a] -> [a] -> [a]
++ FilePath
pname forall a. [a] -> [a] -> [a]
++ FilePath
" v2-exec [FLAGS] [--] COMMAND [--] [ARGS]\n"
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \FilePath
pname -> FilePath -> FilePath
wrapText forall a b. (a -> b) -> a -> b
$
       FilePath
"During development it is often useful to run build tasks and perform"
    forall a. [a] -> [a] -> [a]
++ FilePath
" one-off program executions to experiment with the behavior of build"
    forall a. [a] -> [a] -> [a]
++ FilePath
" tools. It is convenient to run these tools in the same way " forall a. [a] -> [a] -> [a]
++ FilePath
pname
    forall a. [a] -> [a] -> [a]
++ FilePath
" itself would. The `" forall a. [a] -> [a] -> [a]
++ FilePath
pname forall a. [a] -> [a] -> [a]
++ FilePath
" v2-exec` command provides a way to"
    forall a. [a] -> [a] -> [a]
++ FilePath
" do so.\n"
    forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
    forall a. [a] -> [a] -> [a]
++ FilePath
"Compiler tools will be configured to see the same subset of the store"
    forall a. [a] -> [a] -> [a]
++ FilePath
" that builds would see. The PATH is modified to make all executables in"
    forall a. [a] -> [a] -> [a]
++ FilePath
" the dependency tree available (provided they have been built already)."
    forall a. [a] -> [a] -> [a]
++ FilePath
" Commands are also rewritten in the way cabal itself would. For"
    forall a. [a] -> [a] -> [a]
++ FilePath
" example, `" forall a. [a] -> [a] -> [a]
++ FilePath
pname forall a. [a] -> [a] -> [a]
++ FilePath
" v2-exec ghc` will consult the configuration"
    forall a. [a] -> [a] -> [a]
++ FilePath
" to choose an appropriate version of ghc and to include any"
    forall a. [a] -> [a] -> [a]
++ FilePath
" ghc-specific flags requested."
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes = forall a. Maybe a
Nothing
  , commandOptions :: ShowOrParseArgs -> [OptionField (NixStyleFlags ())]
commandOptions      = forall a. [OptionField a] -> [OptionField a]
removeIgnoreProjectOption
                        forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(ShowOrParseArgs -> [OptionField a])
-> ShowOrParseArgs -> [OptionField (NixStyleFlags a)]
nixStyleOptions (forall a b. a -> b -> a
const [])
  , commandDefaultFlags :: NixStyleFlags ()
commandDefaultFlags = forall a. a -> NixStyleFlags a
defaultNixStyleFlags ()
  }

execAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
execAction :: NixStyleFlags () -> [FilePath] -> GlobalFlags -> IO ()
execAction 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
..} [FilePath]
extraArgs GlobalFlags
globalFlags = do

  ProjectBaseContext
baseCtx <- Verbosity
-> ProjectConfig -> CurrentCommand -> IO ProjectBaseContext
establishProjectBaseContext Verbosity
verbosity ProjectConfig
cliConfig CurrentCommand
OtherCommand

  -- To set up the environment, we'd like to select the libraries in our
  -- dependency tree that we've already built. So first we set up an install
  -- plan, but we walk the dependency tree without first executing the plan.
  ProjectBuildContext
buildCtx <- Verbosity
-> ProjectBaseContext
-> (ElaboratedInstallPlan
    -> IO (ElaboratedInstallPlan, TargetsMap))
-> IO ProjectBuildContext
runProjectPreBuildPhase
    Verbosity
verbosity
    ProjectBaseContext
baseCtx
    (\ElaboratedInstallPlan
plan -> forall (m :: * -> *) a. Monad m => a -> m a
return (ElaboratedInstallPlan
plan, forall k a. Map k a
M.empty))

  -- We use the build status below to decide what libraries to include in the
  -- compiler environment, but we don't want to actually build anything. So we
  -- pass mempty to indicate that nothing happened and we just want the current
  -- status.
  PostBuildProjectStatus
buildStatus <- Verbosity
-> DistDirLayout
-> ElaboratedInstallPlan
-> BuildStatusMap
-> BuildOutcomes
-> IO PostBuildProjectStatus
updatePostBuildProjectStatus
    Verbosity
verbosity
    (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx)
    (ProjectBuildContext -> ElaboratedInstallPlan
elaboratedPlanOriginal ProjectBuildContext
buildCtx)
    (ProjectBuildContext -> BuildStatusMap
pkgsBuildStatus ProjectBuildContext
buildCtx)
    forall a. Monoid a => a
mempty

  -- Some dependencies may have executables. Let's put those on the PATH.
  [FilePath]
extraPaths <- Verbosity
-> ProjectBaseContext -> ProjectBuildContext -> IO [FilePath]
pathAdditions Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx
  let programDb :: ProgramDb
programDb = (ProgramSearchPath -> ProgramSearchPath) -> ProgramDb -> ProgramDb
modifyProgramSearchPath
                  (forall a b. (a -> b) -> [a] -> [b]
map FilePath -> ProgramSearchPathEntry
ProgramSearchPathDir [FilePath]
extraPaths forall a. [a] -> [a] -> [a]
++)
                forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs
                forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared
                forall a b. (a -> b) -> a -> b
$ ProjectBuildContext
buildCtx

  -- Now that we have the packages, set up the environment. We accomplish this
  -- by creating an environment file that selects the databases and packages we
  -- computed in the previous step, and setting an environment variable to
  -- point at the file.
  -- In case ghc is too old to support environment files,
  -- we pass the same info as arguments
  let compiler :: Compiler
compiler = ElaboratedSharedConfig -> Compiler
pkgConfigCompiler forall a b. (a -> b) -> a -> b
$ ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx
      envFilesSupported :: Bool
envFilesSupported = GhcImplInfo -> Bool
supportsPkgEnvFiles (Compiler -> GhcImplInfo
getImplInfo Compiler
compiler)
  case [FilePath]
extraArgs of
    [] -> forall a. Verbosity -> FilePath -> IO a
die' Verbosity
verbosity FilePath
"Please specify an executable to run"
    FilePath
exe:[FilePath]
args -> do
      (ConfiguredProgram
program, ProgramDb
_) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity (FilePath -> Program
simpleProgram FilePath
exe) ProgramDb
programDb
      let argOverrides :: [FilePath]
argOverrides =
            Compiler
-> DistDirLayout
-> ElaboratedInstallPlan
-> PostBuildProjectStatus
-> [FilePath]
argsEquivalentOfGhcEnvironmentFile
              Compiler
compiler
              (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx)
              (ProjectBuildContext -> ElaboratedInstallPlan
elaboratedPlanOriginal ProjectBuildContext
buildCtx)
              PostBuildProjectStatus
buildStatus
          programIsConfiguredCompiler :: Bool
programIsConfiguredCompiler = ElaboratedSharedConfig -> ConfiguredProgram -> Bool
matchCompilerPath
                                          (ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx)
                                          ConfiguredProgram
program
          argOverrides' :: [FilePath]
argOverrides' =
            if Bool
envFilesSupported
            Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
programIsConfiguredCompiler
            then []
            else [FilePath]
argOverrides

      (if Bool
envFilesSupported
      then forall a.
Verbosity
-> ProjectBaseContext
-> ProjectBuildContext
-> PostBuildProjectStatus
-> ([(FilePath, Maybe FilePath)] -> IO a)
-> IO a
withTempEnvFile Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx PostBuildProjectStatus
buildStatus
      else \[(FilePath, Maybe FilePath)] -> IO ()
f -> [(FilePath, Maybe FilePath)] -> IO ()
f []) forall a b. (a -> b) -> a -> b
$ \[(FilePath, Maybe FilePath)]
envOverrides -> do
        let program' :: ConfiguredProgram
program'   = [(FilePath, Maybe FilePath)]
-> [FilePath] -> ConfiguredProgram -> ConfiguredProgram
withOverrides
                           [(FilePath, Maybe FilePath)]
envOverrides
                           [FilePath]
argOverrides'
                           ConfiguredProgram
program
            invocation :: ProgramInvocation
invocation = ConfiguredProgram -> [FilePath] -> ProgramInvocation
programInvocation ConfiguredProgram
program' [FilePath]
args
            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 -> FilePath -> IO ()
notice Verbosity
verbosity FilePath
"Running of executable suppressed by flag(s)"
           else Verbosity -> ProgramInvocation -> IO ()
runProgramInvocation Verbosity
verbosity ProgramInvocation
invocation
  where
    verbosity :: Verbosity
verbosity = forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
configFlags)
    cliConfig :: ProjectConfig
cliConfig = forall a.
GlobalFlags
-> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig
commandLineFlagsToProjectConfig GlobalFlags
globalFlags NixStyleFlags ()
flags
                  forall a. Monoid a => a
mempty -- ClientInstallFlags, not needed here
    withOverrides :: [(FilePath, Maybe FilePath)]
-> [FilePath] -> ConfiguredProgram -> ConfiguredProgram
withOverrides [(FilePath, Maybe FilePath)]
env [FilePath]
args ConfiguredProgram
program = ConfiguredProgram
program
      { programOverrideEnv :: [(FilePath, Maybe FilePath)]
programOverrideEnv = ConfiguredProgram -> [(FilePath, Maybe FilePath)]
programOverrideEnv ConfiguredProgram
program forall a. [a] -> [a] -> [a]
++ [(FilePath, Maybe FilePath)]
env
      , programDefaultArgs :: [FilePath]
programDefaultArgs = ConfiguredProgram -> [FilePath]
programDefaultArgs ConfiguredProgram
program forall a. [a] -> [a] -> [a]
++ [FilePath]
args}

matchCompilerPath :: ElaboratedSharedConfig -> ConfiguredProgram -> Bool
matchCompilerPath :: ElaboratedSharedConfig -> ConfiguredProgram -> Bool
matchCompilerPath ElaboratedSharedConfig
elaboratedShared ConfiguredProgram
program =
  ConfiguredProgram -> FilePath
programPath ConfiguredProgram
program
  forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`
  (ConfiguredProgram -> FilePath
programPath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ConfiguredProgram]
configuredCompilers)
  where
    configuredCompilers :: [ConfiguredProgram]
configuredCompilers = ProgramDb -> [ConfiguredProgram]
configuredPrograms forall a b. (a -> b) -> a -> b
$ ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs ElaboratedSharedConfig
elaboratedShared

-- | Execute an action with a temporary .ghc.environment file reflecting the
-- current environment. The action takes an environment containing the env
-- variable which points ghc to the file.
withTempEnvFile :: Verbosity
                -> ProjectBaseContext
                -> ProjectBuildContext
                -> PostBuildProjectStatus
                -> ([(String, Maybe String)] -> IO a)
                -> IO a
withTempEnvFile :: forall a.
Verbosity
-> ProjectBaseContext
-> ProjectBuildContext
-> PostBuildProjectStatus
-> ([(FilePath, Maybe FilePath)] -> IO a)
-> IO a
withTempEnvFile Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx PostBuildProjectStatus
buildStatus [(FilePath, Maybe FilePath)] -> IO a
action = do
  Verbosity -> Bool -> FilePath -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True (DistDirLayout -> FilePath
distTempDirectory (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx))
  forall a.
Verbosity -> FilePath -> FilePath -> (FilePath -> IO a) -> IO a
withTempDirectory
   Verbosity
verbosity
   (DistDirLayout -> FilePath
distTempDirectory (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx))
   FilePath
"environment."
   (\FilePath
tmpDir -> do
     [(FilePath, Maybe FilePath)]
envOverrides <- Verbosity
-> FilePath
-> ElaboratedInstallPlan
-> ElaboratedSharedConfig
-> PostBuildProjectStatus
-> IO [(FilePath, Maybe FilePath)]
createPackageEnvironment
       Verbosity
verbosity
       FilePath
tmpDir
       (ProjectBuildContext -> ElaboratedInstallPlan
elaboratedPlanToExecute ProjectBuildContext
buildCtx)
       (ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx)
       PostBuildProjectStatus
buildStatus
     [(FilePath, Maybe FilePath)] -> IO a
action [(FilePath, Maybe FilePath)]
envOverrides)

pathAdditions :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO [FilePath]
pathAdditions :: Verbosity
-> ProjectBaseContext -> ProjectBuildContext -> IO [FilePath]
pathAdditions Verbosity
verbosity ProjectBaseContext{[PackageSpecifier UnresolvedSourcePackage]
Maybe InstalledPackageIndex
BuildTimeSettings
ProjectConfig
CabalDirLayout
DistDirLayout
CurrentCommand
installedPackages :: ProjectBaseContext -> Maybe InstalledPackageIndex
currentCommand :: ProjectBaseContext -> CurrentCommand
localPackages :: ProjectBaseContext -> [PackageSpecifier UnresolvedSourcePackage]
projectConfig :: ProjectBaseContext -> ProjectConfig
cabalDirLayout :: ProjectBaseContext -> CabalDirLayout
installedPackages :: Maybe InstalledPackageIndex
currentCommand :: CurrentCommand
buildSettings :: BuildTimeSettings
localPackages :: [PackageSpecifier UnresolvedSourcePackage]
projectConfig :: ProjectConfig
cabalDirLayout :: CabalDirLayout
distDirLayout :: DistDirLayout
buildSettings :: ProjectBaseContext -> BuildTimeSettings
distDirLayout :: ProjectBaseContext -> DistDirLayout
..}ProjectBuildContext{TargetsMap
BuildStatusMap
ElaboratedInstallPlan
ElaboratedSharedConfig
targetsMap :: ProjectBuildContext -> TargetsMap
targetsMap :: TargetsMap
pkgsBuildStatus :: BuildStatusMap
elaboratedShared :: ElaboratedSharedConfig
elaboratedPlanToExecute :: ElaboratedInstallPlan
elaboratedPlanOriginal :: ElaboratedInstallPlan
elaboratedPlanToExecute :: ProjectBuildContext -> ElaboratedInstallPlan
elaboratedShared :: ProjectBuildContext -> ElaboratedSharedConfig
pkgsBuildStatus :: ProjectBuildContext -> BuildStatusMap
elaboratedPlanOriginal :: ProjectBuildContext -> ElaboratedInstallPlan
..} = do
  Verbosity -> FilePath -> IO ()
info Verbosity
verbosity forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
unlines forall a b. (a -> b) -> a -> b
$ FilePath
"Including the following directories in PATH:"
                           forall a. a -> [a] -> [a]
: [FilePath]
paths
  forall (m :: * -> *) a. Monad m => a -> m a
return [FilePath]
paths
  where
  paths :: [FilePath]
paths = forall a. Set a -> [a]
S.toList
        forall a b. (a -> b) -> a -> b
$ DistDirLayout
-> ElaboratedSharedConfig -> ElaboratedInstallPlan -> Set FilePath
binDirectories DistDirLayout
distDirLayout ElaboratedSharedConfig
elaboratedShared ElaboratedInstallPlan
elaboratedPlanToExecute

binDirectories
  :: DistDirLayout
  -> ElaboratedSharedConfig
  -> ElaboratedInstallPlan
  -> Set FilePath
binDirectories :: DistDirLayout
-> ElaboratedSharedConfig -> ElaboratedInstallPlan -> Set FilePath
binDirectories DistDirLayout
layout ElaboratedSharedConfig
config = forall {ipkg}.
GenericInstallPlan ipkg ElaboratedConfiguredPackage -> Set FilePath
fromElaboratedInstallPlan where
  fromElaboratedInstallPlan :: GenericInstallPlan ipkg ElaboratedConfiguredPackage -> Set FilePath
fromElaboratedInstallPlan = forall {ipkg}.
Graph (GenericPlanPackage ipkg ElaboratedConfiguredPackage)
-> Set FilePath
fromGraph forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ipkg srcpkg.
GenericInstallPlan ipkg srcpkg
-> Graph (GenericPlanPackage ipkg srcpkg)
toGraph
  fromGraph :: Graph (GenericPlanPackage ipkg ElaboratedConfiguredPackage)
-> Set FilePath
fromGraph = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall {ipkg}.
GenericPlanPackage ipkg ElaboratedConfiguredPackage -> Set FilePath
fromPlan
  fromSrcPkg :: ElaboratedConfiguredPackage -> Set FilePath
fromSrcPkg = forall a. Ord a => [a] -> Set a
S.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. DistDirLayout
-> ElaboratedSharedConfig
-> ElaboratedConfiguredPackage
-> [FilePath]
Planning.binDirectories DistDirLayout
layout ElaboratedSharedConfig
config

  fromPlan :: GenericPlanPackage ipkg ElaboratedConfiguredPackage -> Set FilePath
fromPlan (PreExisting ipkg
_) = forall a. Monoid a => a
mempty
  fromPlan (Configured ElaboratedConfiguredPackage
pkg) = ElaboratedConfiguredPackage -> Set FilePath
fromSrcPkg ElaboratedConfiguredPackage
pkg
  fromPlan (Installed ElaboratedConfiguredPackage
pkg) = ElaboratedConfiguredPackage -> Set FilePath
fromSrcPkg ElaboratedConfiguredPackage
pkg