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

execAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
execAction :: NixStyleFlags () -> [String] -> 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
..} [String]
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 -> (ElaboratedInstallPlan, TargetsMap)
-> IO (ElaboratedInstallPlan, TargetsMap)
forall (m :: * -> *) a. Monad m => a -> m a
return (ElaboratedInstallPlan
plan, TargetsMap
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)
    BuildOutcomes
forall a. Monoid a => a
mempty

  -- Some dependencies may have executables. Let's put those on the PATH.
  [String]
extraPaths <- Verbosity
-> ProjectBaseContext -> ProjectBuildContext -> IO [String]
pathAdditions Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx
  let programDb :: ProgramDb
programDb = (ProgramSearchPath -> ProgramSearchPath) -> ProgramDb -> ProgramDb
modifyProgramSearchPath
                  ((String -> ProgramSearchPathEntry) -> [String] -> ProgramSearchPath
forall a b. (a -> b) -> [a] -> [b]
map String -> ProgramSearchPathEntry
ProgramSearchPathDir [String]
extraPaths ProgramSearchPath -> ProgramSearchPath -> ProgramSearchPath
forall a. [a] -> [a] -> [a]
++)
                (ProgramDb -> ProgramDb)
-> (ProjectBuildContext -> ProgramDb)
-> ProjectBuildContext
-> ProgramDb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs
                (ElaboratedSharedConfig -> ProgramDb)
-> (ProjectBuildContext -> ElaboratedSharedConfig)
-> ProjectBuildContext
-> ProgramDb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared
                (ProjectBuildContext -> ProgramDb)
-> ProjectBuildContext -> ProgramDb
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 (ElaboratedSharedConfig -> Compiler)
-> ElaboratedSharedConfig -> Compiler
forall a b. (a -> b) -> a -> b
$ ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx
      envFilesSupported :: Bool
envFilesSupported = GhcImplInfo -> Bool
supportsPkgEnvFiles (Compiler -> GhcImplInfo
getImplInfo Compiler
compiler)
  case [String]
extraArgs of
    [] -> Verbosity -> String -> IO ()
forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity String
"Please specify an executable to run"
    String
exe:[String]
args -> do
      (ConfiguredProgram
program, ProgramDb
_) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity (String -> Program
simpleProgram String
exe) ProgramDb
programDb
      let argOverrides :: [String]
argOverrides =
            Compiler
-> DistDirLayout
-> ElaboratedInstallPlan
-> PostBuildProjectStatus
-> [String]
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' :: [String]
argOverrides' =
            if Bool
envFilesSupported
            Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
programIsConfiguredCompiler
            then []
            else [String]
argOverrides

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

matchCompilerPath :: ElaboratedSharedConfig -> ConfiguredProgram -> Bool
matchCompilerPath :: ElaboratedSharedConfig -> ConfiguredProgram -> Bool
matchCompilerPath ElaboratedSharedConfig
elaboratedShared ConfiguredProgram
program =
  ConfiguredProgram -> String
programPath ConfiguredProgram
program
  String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`
  (ConfiguredProgram -> String
programPath (ConfiguredProgram -> String) -> [ConfiguredProgram] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ConfiguredProgram]
configuredCompilers)
  where
    configuredCompilers :: [ConfiguredProgram]
configuredCompilers = ProgramDb -> [ConfiguredProgram]
configuredPrograms (ProgramDb -> [ConfiguredProgram])
-> ProgramDb -> [ConfiguredProgram]
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 :: Verbosity
-> ProjectBaseContext
-> ProjectBuildContext
-> PostBuildProjectStatus
-> ([(String, Maybe String)] -> IO a)
-> IO a
withTempEnvFile Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx PostBuildProjectStatus
buildStatus [(String, Maybe String)] -> IO a
action = do
  Verbosity -> Bool -> String -> IO ()
createDirectoryIfMissingVerbose Verbosity
verbosity Bool
True (DistDirLayout -> String
distTempDirectory (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx))
  Verbosity -> String -> String -> (String -> IO a) -> IO a
forall a. Verbosity -> String -> String -> (String -> IO a) -> IO a
withTempDirectory
   Verbosity
verbosity
   (DistDirLayout -> String
distTempDirectory (ProjectBaseContext -> DistDirLayout
distDirLayout ProjectBaseContext
baseCtx))
   String
"environment."
   (\String
tmpDir -> do
     [(String, Maybe String)]
envOverrides <- Verbosity
-> String
-> ElaboratedInstallPlan
-> ElaboratedSharedConfig
-> PostBuildProjectStatus
-> IO [(String, Maybe String)]
createPackageEnvironment
       Verbosity
verbosity
       String
tmpDir
       (ProjectBuildContext -> ElaboratedInstallPlan
elaboratedPlanToExecute ProjectBuildContext
buildCtx)
       (ProjectBuildContext -> ElaboratedSharedConfig
elaboratedShared ProjectBuildContext
buildCtx)
       PostBuildProjectStatus
buildStatus
     [(String, Maybe String)] -> IO a
action [(String, Maybe String)]
envOverrides)

pathAdditions :: Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO [FilePath]
pathAdditions :: Verbosity
-> ProjectBaseContext -> ProjectBuildContext -> IO [String]
pathAdditions Verbosity
verbosity ProjectBaseContext{[PackageSpecifier UnresolvedSourcePackage]
CabalDirLayout
DistDirLayout
BuildTimeSettings
ProjectConfig
CurrentCommand
currentCommand :: ProjectBaseContext -> CurrentCommand
localPackages :: ProjectBaseContext -> [PackageSpecifier UnresolvedSourcePackage]
projectConfig :: ProjectBaseContext -> ProjectConfig
cabalDirLayout :: ProjectBaseContext -> CabalDirLayout
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 -> String -> IO ()
info Verbosity
verbosity (String -> IO ()) -> ([String] -> String) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines ([String] -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Including the following directories in PATH:"
                           String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
paths
  [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return [String]
paths
  where
  paths :: [String]
paths = Set String -> [String]
forall a. Set a -> [a]
S.toList
        (Set String -> [String]) -> Set String -> [String]
forall a b. (a -> b) -> a -> b
$ DistDirLayout
-> ElaboratedSharedConfig -> ElaboratedInstallPlan -> Set String
binDirectories DistDirLayout
distDirLayout ElaboratedSharedConfig
elaboratedShared ElaboratedInstallPlan
elaboratedPlanToExecute

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

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