{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Distribution.Client.ProjectPlanning.Types
( SolverInstallPlan
, ElaboratedInstallPlan
, normaliseConfiguredPackage
, ElaboratedConfiguredPackage (..)
, showElaboratedInstallPlan
, elabDistDirParams
, elabExeDependencyPaths
, elabLibDependencies
, elabOrderLibDependencies
, elabExeDependencies
, elabOrderExeDependencies
, elabSetupDependencies
, elabPkgConfigDependencies
, elabInplaceDependencyBuildCacheFiles
, elabRequiresRegistration
, dataDirsEnvironmentForPlan
, elabPlanPackageName
, elabConfiguredName
, elabComponentName
, ElaboratedPackageOrComponent (..)
, ElaboratedComponent (..)
, ElaboratedPackage (..)
, pkgOrderDependencies
, ElaboratedPlanPackage
, ElaboratedSharedConfig (..)
, ElaboratedReadyPackage
, BuildStyle (..)
, MemoryOrDisk (..)
, isInplaceBuildStyle
, CabalFileText
, NotPerComponentReason (..)
, NotPerComponentBuildType (..)
, whyNotPerComponent
, ComponentTarget (..)
, showComponentTarget
, showTestComponentTarget
, showBenchComponentTarget
, SubComponentTarget (..)
, isSubLibComponentTarget
, isForeignLibComponentTarget
, isExeComponentTarget
, isTestComponentTarget
, isBenchComponentTarget
, componentOptionalStanza
, SetupScriptStyle (..)
) where
import Distribution.Client.Compat.Prelude
import Prelude ()
import Distribution.Client.PackageHash
import Distribution.Client.TargetSelector
( SubComponentTarget (..)
)
import Distribution.Client.DistDirLayout
import Distribution.Client.InstallPlan
( GenericInstallPlan
, GenericPlanPackage (..)
)
import qualified Distribution.Client.InstallPlan as InstallPlan
import Distribution.Client.SolverInstallPlan
( SolverInstallPlan
)
import Distribution.Client.Types
import Distribution.Backpack
import Distribution.Backpack.ModuleShape
import Distribution.InstalledPackageInfo (InstalledPackageInfo)
import Distribution.ModuleName (ModuleName)
import Distribution.Package
import qualified Distribution.PackageDescription as Cabal
import Distribution.Simple.Build.PathsModule (pkgPathEnvVar)
import qualified Distribution.Simple.BuildTarget as Cabal
import Distribution.Simple.Compiler
import Distribution.Simple.InstallDirs (PathTemplate)
import qualified Distribution.Simple.InstallDirs as InstallDirs
import Distribution.Simple.LocalBuildInfo
( ComponentName (..)
, LibraryName (..)
)
import Distribution.Simple.Program
import Distribution.Simple.Setup
( DumpBuildInfo (..)
, HaddockTarget
, ReplOptions
, TestShowDetails
)
import Distribution.System
import Distribution.Types.ComponentRequestedSpec
import qualified Distribution.Types.LocalBuildConfig as LBC
import Distribution.Types.PackageDescription (PackageDescription (..))
import Distribution.Types.PkgconfigVersion
import Distribution.Verbosity (normal)
import Distribution.Version
import Distribution.Compat.Graph (IsNode (..))
import Distribution.Simple.Utils (ordNub)
import Distribution.Solver.Types.ComponentDeps (ComponentDeps)
import qualified Distribution.Solver.Types.ComponentDeps as CD
import Distribution.Solver.Types.OptionalStanza
import qualified Data.ByteString.Lazy as LBS
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as Map
import qualified Data.Monoid as Mon
import System.FilePath ((</>))
import Text.PrettyPrint (hsep, parens, text)
type ElaboratedInstallPlan =
GenericInstallPlan
InstalledPackageInfo
ElaboratedConfiguredPackage
type ElaboratedPlanPackage =
GenericPlanPackage
InstalledPackageInfo
ElaboratedConfiguredPackage
elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> String
elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> FilePath
elabPlanPackageName Verbosity
verbosity (PreExisting InstalledPackageInfo
ipkg)
| Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
<= Verbosity
normal = PackageName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (InstalledPackageInfo -> PackageName
forall pkg. Package pkg => pkg -> PackageName
packageName InstalledPackageInfo
ipkg)
| Bool
otherwise = UnitId -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (InstalledPackageInfo -> UnitId
forall pkg. HasUnitId pkg => pkg -> UnitId
installedUnitId InstalledPackageInfo
ipkg)
elabPlanPackageName Verbosity
verbosity (Configured ElaboratedConfiguredPackage
elab) =
Verbosity -> ElaboratedConfiguredPackage -> FilePath
elabConfiguredName Verbosity
verbosity ElaboratedConfiguredPackage
elab
elabPlanPackageName Verbosity
verbosity (Installed ElaboratedConfiguredPackage
elab) =
Verbosity -> ElaboratedConfiguredPackage -> FilePath
elabConfiguredName Verbosity
verbosity ElaboratedConfiguredPackage
elab
showElaboratedInstallPlan :: ElaboratedInstallPlan -> String
showElaboratedInstallPlan :: ElaboratedInstallPlan -> FilePath
showElaboratedInstallPlan = (ElaboratedPlanPackage -> ShowPlanNode)
-> ElaboratedInstallPlan -> FilePath
forall ipkg srcpkg.
(GenericPlanPackage ipkg srcpkg -> ShowPlanNode)
-> GenericInstallPlan ipkg srcpkg -> FilePath
InstallPlan.showInstallPlan_gen ElaboratedPlanPackage -> ShowPlanNode
forall {ipkg}.
(Key ipkg ~ UnitId, Package ipkg, IsNode ipkg) =>
GenericPlanPackage ipkg ElaboratedConfiguredPackage -> ShowPlanNode
showNode
where
showNode :: GenericPlanPackage ipkg ElaboratedConfiguredPackage -> ShowPlanNode
showNode GenericPlanPackage ipkg ElaboratedConfiguredPackage
pkg =
InstallPlan.ShowPlanNode
{ showPlanHerald :: Doc
InstallPlan.showPlanHerald = Doc
herald
, showPlanNeighbours :: [Doc]
InstallPlan.showPlanNeighbours = [Doc]
deps
}
where
herald :: Doc
herald =
( [Doc] -> Doc
hsep
[ FilePath -> Doc
text (GenericPlanPackage ipkg ElaboratedConfiguredPackage -> FilePath
forall ipkg srcpkg. GenericPlanPackage ipkg srcpkg -> FilePath
InstallPlan.showPlanPackageTag GenericPlanPackage ipkg ElaboratedConfiguredPackage
pkg)
, (ipkg -> Doc)
-> (ElaboratedConfiguredPackage -> Doc)
-> GenericPlanPackage ipkg ElaboratedConfiguredPackage
-> Doc
forall ipkg a srcpkg.
(ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a
InstallPlan.foldPlanPackage (Doc -> ipkg -> Doc
forall a b. a -> b -> a
const Doc
forall a. Monoid a => a
mempty) ElaboratedConfiguredPackage -> Doc
in_mem GenericPlanPackage ipkg ElaboratedConfiguredPackage
pkg
, PackageIdentifier -> Doc
forall a. Pretty a => a -> Doc
pretty (GenericPlanPackage ipkg ElaboratedConfiguredPackage
-> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId GenericPlanPackage ipkg ElaboratedConfiguredPackage
pkg)
, Doc -> Doc
parens (UnitId -> Doc
forall a. Pretty a => a -> Doc
pretty (GenericPlanPackage ipkg ElaboratedConfiguredPackage
-> Key (GenericPlanPackage ipkg ElaboratedConfiguredPackage)
forall a. IsNode a => a -> Key a
nodeKey GenericPlanPackage ipkg ElaboratedConfiguredPackage
pkg))
]
)
in_mem :: ElaboratedConfiguredPackage -> Doc
in_mem ElaboratedConfiguredPackage
elab = case ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle ElaboratedConfiguredPackage
elab of
BuildInplaceOnly MemoryOrDisk
InMemory -> Doc -> Doc
parens (FilePath -> Doc
text FilePath
"In Memory")
BuildStyle
_ -> Doc
forall a. Monoid a => a
mempty
deps :: [Doc]
deps = (ipkg -> [Doc])
-> (ElaboratedConfiguredPackage -> [Doc])
-> GenericPlanPackage ipkg ElaboratedConfiguredPackage
-> [Doc]
forall ipkg a srcpkg.
(ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a
InstallPlan.foldPlanPackage ipkg -> [Doc]
installed_deps ElaboratedConfiguredPackage -> [Doc]
local_deps GenericPlanPackage ipkg ElaboratedConfiguredPackage
pkg
installed_deps :: ipkg -> [Doc]
installed_deps = (Key ipkg -> Doc) -> [Key ipkg] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Key ipkg -> Doc
forall a. Pretty a => a -> Doc
pretty ([Key ipkg] -> [Doc]) -> (ipkg -> [Key ipkg]) -> ipkg -> [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ipkg -> [Key ipkg]
forall a. IsNode a => a -> [Key a]
nodeNeighbors
local_deps :: ElaboratedConfiguredPackage -> [Doc]
local_deps ElaboratedConfiguredPackage
cfg = [(if Bool
internal then FilePath -> Doc
text FilePath
"+" else Doc
forall a. Monoid a => a
mempty) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> ComponentId -> Doc
forall a. Pretty a => a -> Doc
pretty (ConfiguredId -> ComponentId
confInstId ConfiguredId
uid) | (ConfiguredId
uid, Bool
internal) <- ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)]
elabLibDependencies ElaboratedConfiguredPackage
cfg]
data ElaboratedSharedConfig = ElaboratedSharedConfig
{ ElaboratedSharedConfig -> Platform
pkgConfigPlatform :: Platform
, ElaboratedSharedConfig -> Compiler
pkgConfigCompiler :: Compiler
, ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs :: ProgramDb
, ElaboratedSharedConfig -> ReplOptions
pkgConfigReplOptions :: ReplOptions
}
deriving (Int -> ElaboratedSharedConfig -> ShowS
[ElaboratedSharedConfig] -> ShowS
ElaboratedSharedConfig -> FilePath
(Int -> ElaboratedSharedConfig -> ShowS)
-> (ElaboratedSharedConfig -> FilePath)
-> ([ElaboratedSharedConfig] -> ShowS)
-> Show ElaboratedSharedConfig
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElaboratedSharedConfig -> ShowS
showsPrec :: Int -> ElaboratedSharedConfig -> ShowS
$cshow :: ElaboratedSharedConfig -> FilePath
show :: ElaboratedSharedConfig -> FilePath
$cshowList :: [ElaboratedSharedConfig] -> ShowS
showList :: [ElaboratedSharedConfig] -> ShowS
Show, (forall x. ElaboratedSharedConfig -> Rep ElaboratedSharedConfig x)
-> (forall x.
Rep ElaboratedSharedConfig x -> ElaboratedSharedConfig)
-> Generic ElaboratedSharedConfig
forall x. Rep ElaboratedSharedConfig x -> ElaboratedSharedConfig
forall x. ElaboratedSharedConfig -> Rep ElaboratedSharedConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ElaboratedSharedConfig -> Rep ElaboratedSharedConfig x
from :: forall x. ElaboratedSharedConfig -> Rep ElaboratedSharedConfig x
$cto :: forall x. Rep ElaboratedSharedConfig x -> ElaboratedSharedConfig
to :: forall x. Rep ElaboratedSharedConfig x -> ElaboratedSharedConfig
Generic, Typeable)
instance Binary ElaboratedSharedConfig
instance Structured ElaboratedSharedConfig
data ElaboratedConfiguredPackage = ElaboratedConfiguredPackage
{ ElaboratedConfiguredPackage -> UnitId
elabUnitId :: UnitId
, ElaboratedConfiguredPackage -> ComponentId
elabComponentId :: ComponentId
, ElaboratedConfiguredPackage -> Map ModuleName Module
elabInstantiatedWith :: Map ModuleName Module
, ElaboratedConfiguredPackage -> Map ModuleName OpenModule
elabLinkedInstantiatedWith :: Map ModuleName OpenModule
, ElaboratedConfiguredPackage -> Bool
elabIsCanonical :: Bool
, ElaboratedConfiguredPackage -> PackageIdentifier
elabPkgSourceId :: PackageId
, ElaboratedConfiguredPackage -> ModuleShape
elabModuleShape :: ModuleShape
, ElaboratedConfiguredPackage -> FlagAssignment
elabFlagAssignment :: Cabal.FlagAssignment
, ElaboratedConfiguredPackage -> FlagAssignment
elabFlagDefaults :: Cabal.FlagAssignment
, ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription :: Cabal.PackageDescription
, ElaboratedConfiguredPackage -> PackageLocation (Maybe FilePath)
elabPkgSourceLocation :: PackageLocation (Maybe FilePath)
, ElaboratedConfiguredPackage -> Maybe PackageSourceHash
elabPkgSourceHash :: Maybe PackageSourceHash
, ElaboratedConfiguredPackage -> Bool
elabLocalToProject :: Bool
, ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle :: BuildStyle
, ElaboratedConfiguredPackage -> ComponentRequestedSpec
elabEnabledSpec :: ComponentRequestedSpec
, ElaboratedConfiguredPackage -> OptionalStanzaSet
elabStanzasAvailable :: OptionalStanzaSet
, ElaboratedConfiguredPackage -> OptionalStanzaMap (Maybe Bool)
elabStanzasRequested :: OptionalStanzaMap (Maybe Bool)
, ElaboratedConfiguredPackage -> [Maybe PackageDB]
elabPackageDbs :: [Maybe PackageDB]
, ElaboratedConfiguredPackage -> PackageDBStack
elabSetupPackageDBStack :: PackageDBStack
, ElaboratedConfiguredPackage -> PackageDBStack
elabBuildPackageDBStack :: PackageDBStack
, ElaboratedConfiguredPackage -> PackageDBStack
elabRegisterPackageDBStack :: PackageDBStack
, ElaboratedConfiguredPackage -> PackageDBStack
elabInplaceSetupPackageDBStack :: PackageDBStack
, ElaboratedConfiguredPackage -> PackageDBStack
elabInplaceBuildPackageDBStack :: PackageDBStack
, ElaboratedConfiguredPackage -> PackageDBStack
elabInplaceRegisterPackageDBStack :: PackageDBStack
, ElaboratedConfiguredPackage -> Maybe CabalFileText
elabPkgDescriptionOverride :: Maybe CabalFileText
,
ElaboratedConfiguredPackage -> BuildOptions
elabBuildOptions :: LBC.BuildOptions
, ElaboratedConfiguredPackage -> DumpBuildInfo
elabDumpBuildInfo :: DumpBuildInfo
, ElaboratedConfiguredPackage -> Map FilePath FilePath
elabProgramPaths :: Map String FilePath
, ElaboratedConfiguredPackage -> Map FilePath [FilePath]
elabProgramArgs :: Map String [String]
, :: [FilePath]
, ElaboratedConfiguredPackage -> [FilePath]
elabConfigureScriptArgs :: [String]
, :: [FilePath]
, :: [FilePath]
, :: [FilePath]
, :: [FilePath]
, ElaboratedConfiguredPackage -> Maybe PathTemplate
elabProgPrefix :: Maybe PathTemplate
, ElaboratedConfiguredPackage -> Maybe PathTemplate
elabProgSuffix :: Maybe PathTemplate
, ElaboratedConfiguredPackage -> InstallDirs FilePath
elabInstallDirs :: InstallDirs.InstallDirs FilePath
, ElaboratedConfiguredPackage -> Bool
elabHaddockHoogle :: Bool
, ElaboratedConfiguredPackage -> Bool
elabHaddockHtml :: Bool
, ElaboratedConfiguredPackage -> Maybe FilePath
elabHaddockHtmlLocation :: Maybe String
, ElaboratedConfiguredPackage -> Bool
elabHaddockForeignLibs :: Bool
, ElaboratedConfiguredPackage -> HaddockTarget
elabHaddockForHackage :: HaddockTarget
, ElaboratedConfiguredPackage -> Bool
elabHaddockExecutables :: Bool
, ElaboratedConfiguredPackage -> Bool
elabHaddockTestSuites :: Bool
, ElaboratedConfiguredPackage -> Bool
elabHaddockBenchmarks :: Bool
, ElaboratedConfiguredPackage -> Bool
elabHaddockInternal :: Bool
, ElaboratedConfiguredPackage -> Maybe FilePath
elabHaddockCss :: Maybe FilePath
, ElaboratedConfiguredPackage -> Bool
elabHaddockLinkedSource :: Bool
, ElaboratedConfiguredPackage -> Bool
elabHaddockQuickJump :: Bool
, ElaboratedConfiguredPackage -> Maybe FilePath
elabHaddockHscolourCss :: Maybe FilePath
, ElaboratedConfiguredPackage -> Maybe PathTemplate
elabHaddockContents :: Maybe PathTemplate
, ElaboratedConfiguredPackage -> Maybe PathTemplate
elabHaddockIndex :: Maybe PathTemplate
, ElaboratedConfiguredPackage -> Maybe FilePath
elabHaddockBaseUrl :: Maybe String
, ElaboratedConfiguredPackage -> Maybe FilePath
elabHaddockLib :: Maybe String
, ElaboratedConfiguredPackage -> Maybe FilePath
elabHaddockOutputDir :: Maybe FilePath
, ElaboratedConfiguredPackage -> Maybe PathTemplate
elabTestMachineLog :: Maybe PathTemplate
, ElaboratedConfiguredPackage -> Maybe PathTemplate
elabTestHumanLog :: Maybe PathTemplate
, ElaboratedConfiguredPackage -> Maybe TestShowDetails
elabTestShowDetails :: Maybe TestShowDetails
, ElaboratedConfiguredPackage -> Bool
elabTestKeepTix :: Bool
, ElaboratedConfiguredPackage -> Maybe FilePath
elabTestWrapper :: Maybe FilePath
, ElaboratedConfiguredPackage -> Bool
elabTestFailWhenNoTestSuites :: Bool
, ElaboratedConfiguredPackage -> [PathTemplate]
elabTestTestOptions :: [PathTemplate]
, ElaboratedConfiguredPackage -> [PathTemplate]
elabBenchmarkOptions :: [PathTemplate]
,
ElaboratedConfiguredPackage -> SetupScriptStyle
elabSetupScriptStyle :: SetupScriptStyle
, ElaboratedConfiguredPackage -> Version
elabSetupScriptCliVersion :: Version
,
ElaboratedConfiguredPackage -> [ComponentTarget]
elabConfigureTargets :: [ComponentTarget]
, ElaboratedConfiguredPackage -> [ComponentTarget]
elabBuildTargets :: [ComponentTarget]
, ElaboratedConfiguredPackage -> [ComponentTarget]
elabTestTargets :: [ComponentTarget]
, ElaboratedConfiguredPackage -> [ComponentTarget]
elabBenchTargets :: [ComponentTarget]
, ElaboratedConfiguredPackage -> [ComponentTarget]
elabReplTarget :: [ComponentTarget]
, ElaboratedConfiguredPackage -> [ComponentTarget]
elabHaddockTargets :: [ComponentTarget]
, ElaboratedConfiguredPackage -> Bool
elabBuildHaddocks :: Bool
,
ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp :: ElaboratedPackageOrComponent
}
deriving (ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
(ElaboratedConfiguredPackage
-> ElaboratedConfiguredPackage -> Bool)
-> (ElaboratedConfiguredPackage
-> ElaboratedConfiguredPackage -> Bool)
-> Eq ElaboratedConfiguredPackage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
== :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
$c/= :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
/= :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
Eq, Int -> ElaboratedConfiguredPackage -> ShowS
[ElaboratedConfiguredPackage] -> ShowS
ElaboratedConfiguredPackage -> FilePath
(Int -> ElaboratedConfiguredPackage -> ShowS)
-> (ElaboratedConfiguredPackage -> FilePath)
-> ([ElaboratedConfiguredPackage] -> ShowS)
-> Show ElaboratedConfiguredPackage
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElaboratedConfiguredPackage -> ShowS
showsPrec :: Int -> ElaboratedConfiguredPackage -> ShowS
$cshow :: ElaboratedConfiguredPackage -> FilePath
show :: ElaboratedConfiguredPackage -> FilePath
$cshowList :: [ElaboratedConfiguredPackage] -> ShowS
showList :: [ElaboratedConfiguredPackage] -> ShowS
Show, (forall x.
ElaboratedConfiguredPackage -> Rep ElaboratedConfiguredPackage x)
-> (forall x.
Rep ElaboratedConfiguredPackage x -> ElaboratedConfiguredPackage)
-> Generic ElaboratedConfiguredPackage
forall x.
Rep ElaboratedConfiguredPackage x -> ElaboratedConfiguredPackage
forall x.
ElaboratedConfiguredPackage -> Rep ElaboratedConfiguredPackage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ElaboratedConfiguredPackage -> Rep ElaboratedConfiguredPackage x
from :: forall x.
ElaboratedConfiguredPackage -> Rep ElaboratedConfiguredPackage x
$cto :: forall x.
Rep ElaboratedConfiguredPackage x -> ElaboratedConfiguredPackage
to :: forall x.
Rep ElaboratedConfiguredPackage x -> ElaboratedConfiguredPackage
Generic, Typeable)
normaliseConfiguredPackage
:: ElaboratedSharedConfig
-> ElaboratedConfiguredPackage
-> ElaboratedConfiguredPackage
normaliseConfiguredPackage :: ElaboratedSharedConfig
-> ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
normaliseConfiguredPackage ElaboratedSharedConfig{ProgramDb
pkgConfigCompilerProgs :: ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs :: ProgramDb
pkgConfigCompilerProgs} ElaboratedConfiguredPackage
pkg =
ElaboratedConfiguredPackage
pkg{elabProgramArgs = Map.mapMaybeWithKey lookupFilter (elabProgramArgs pkg)}
where
knownProgramDb :: ProgramDb
knownProgramDb = [Program] -> ProgramDb -> ProgramDb
addKnownPrograms [Program]
builtinPrograms ProgramDb
pkgConfigCompilerProgs
pkgDesc :: PackageDescription
pkgDesc :: PackageDescription
pkgDesc = ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
pkg
removeEmpty :: [String] -> Maybe [String]
removeEmpty :: [FilePath] -> Maybe [FilePath]
removeEmpty [] = Maybe [FilePath]
forall a. Maybe a
Nothing
removeEmpty [FilePath]
xs = [FilePath] -> Maybe [FilePath]
forall a. a -> Maybe a
Just [FilePath]
xs
lookupFilter :: String -> [String] -> Maybe [String]
lookupFilter :: FilePath -> [FilePath] -> Maybe [FilePath]
lookupFilter FilePath
n [FilePath]
args = [FilePath] -> Maybe [FilePath]
removeEmpty ([FilePath] -> Maybe [FilePath]) -> [FilePath] -> Maybe [FilePath]
forall a b. (a -> b) -> a -> b
$ case FilePath -> ProgramDb -> Maybe Program
lookupKnownProgram FilePath
n ProgramDb
knownProgramDb of
Just Program
p -> Program
-> Maybe Version -> PackageDescription -> [FilePath] -> [FilePath]
programNormaliseArgs Program
p (Program -> Maybe Version
getVersion Program
p) PackageDescription
pkgDesc [FilePath]
args
Maybe Program
Nothing -> [FilePath]
args
getVersion :: Program -> Maybe Version
getVersion :: Program -> Maybe Version
getVersion Program
p = Program -> ProgramDb -> Maybe ConfiguredProgram
lookupProgram Program
p ProgramDb
knownProgramDb Maybe ConfiguredProgram
-> (ConfiguredProgram -> Maybe Version) -> Maybe Version
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ConfiguredProgram -> Maybe Version
programVersion
elabRequiresRegistration :: ElaboratedConfiguredPackage -> Bool
elabRequiresRegistration :: ElaboratedConfiguredPackage -> Bool
elabRequiresRegistration ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabComponent ElaboratedComponent
comp ->
case ElaboratedComponent -> Maybe ComponentName
compComponentName ElaboratedComponent
comp of
Just ComponentName
cn -> ComponentName -> Bool
is_lib ComponentName
cn Bool -> Bool -> Bool
&& Bool
build_target
Maybe ComponentName
_ -> Bool
False
ElabPackage ElaboratedPackage
pkg ->
Bool
build_target
Bool -> Bool -> Bool
|| ( ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle ElaboratedConfiguredPackage
elab BuildStyle -> BuildStyle -> Bool
forall a. Eq a => a -> a -> Bool
== BuildStyle
BuildAndInstall
Bool -> Bool -> Bool
&& PackageDescription -> Bool
Cabal.hasPublicLib (ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
elab)
)
Bool -> Bool -> Bool
|| (ComponentTarget -> Bool) -> [ComponentTarget] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (ElaboratedPackage -> ComponentTarget -> Bool
depends_on_lib ElaboratedPackage
pkg) (ElaboratedConfiguredPackage -> [ComponentTarget]
elabBuildTargets ElaboratedConfiguredPackage
elab)
where
depends_on_lib :: ElaboratedPackage -> ComponentTarget -> Bool
depends_on_lib ElaboratedPackage
pkg (ComponentTarget ComponentName
cn SubComponentTarget
_) =
Bool -> Bool
not
( [()] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null
( (Component -> Bool) -> ComponentDeps [()] -> [()]
forall a. Monoid a => (Component -> Bool) -> ComponentDeps a -> a
CD.select
(Component -> Component -> Bool
forall a. Eq a => a -> a -> Bool
== ComponentName -> Component
CD.componentNameToComponent ComponentName
cn)
(ElaboratedPackage -> ComponentDeps [()]
pkgDependsOnSelfLib ElaboratedPackage
pkg)
)
)
build_target :: Bool
build_target =
if Bool -> Bool
not ([ComponentTarget] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (ElaboratedConfiguredPackage -> [ComponentTarget]
elabBuildTargets ElaboratedConfiguredPackage
elab))
then (ComponentTarget -> Bool) -> [ComponentTarget] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ComponentTarget -> Bool
is_lib_target (ElaboratedConfiguredPackage -> [ComponentTarget]
elabBuildTargets ElaboratedConfiguredPackage
elab)
else
PackageDescription -> Bool
Cabal.hasLibs (ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
elab)
is_lib_target :: ComponentTarget -> Bool
is_lib_target (ComponentTarget ComponentName
cn SubComponentTarget
WholeComponent) = ComponentName -> Bool
is_lib ComponentName
cn
is_lib_target ComponentTarget
_ = Bool
False
is_lib :: ComponentName -> Bool
is_lib (CLibName LibraryName
_) = Bool
True
is_lib ComponentName
_ = Bool
False
dataDirsEnvironmentForPlan
:: DistDirLayout
-> ElaboratedInstallPlan
-> [(String, Maybe FilePath)]
dataDirsEnvironmentForPlan :: DistDirLayout
-> ElaboratedInstallPlan -> [(FilePath, Maybe FilePath)]
dataDirsEnvironmentForPlan DistDirLayout
distDirLayout =
[Maybe (FilePath, Maybe FilePath)] -> [(FilePath, Maybe FilePath)]
forall a. [Maybe a] -> [a]
catMaybes
([Maybe (FilePath, Maybe FilePath)]
-> [(FilePath, Maybe FilePath)])
-> (ElaboratedInstallPlan -> [Maybe (FilePath, Maybe FilePath)])
-> ElaboratedInstallPlan
-> [(FilePath, Maybe FilePath)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ElaboratedPlanPackage -> Maybe (FilePath, Maybe FilePath))
-> [ElaboratedPlanPackage] -> [Maybe (FilePath, Maybe FilePath)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
( (InstalledPackageInfo -> Maybe (FilePath, Maybe FilePath))
-> (ElaboratedConfiguredPackage
-> Maybe (FilePath, Maybe FilePath))
-> ElaboratedPlanPackage
-> Maybe (FilePath, Maybe FilePath)
forall ipkg a srcpkg.
(ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a
InstallPlan.foldPlanPackage
(Maybe (FilePath, Maybe FilePath)
-> InstalledPackageInfo -> Maybe (FilePath, Maybe FilePath)
forall a b. a -> b -> a
const Maybe (FilePath, Maybe FilePath)
forall a. Maybe a
Nothing)
(DistDirLayout
-> ElaboratedConfiguredPackage -> Maybe (FilePath, Maybe FilePath)
dataDirEnvVarForPackage DistDirLayout
distDirLayout)
)
([ElaboratedPlanPackage] -> [Maybe (FilePath, Maybe FilePath)])
-> (ElaboratedInstallPlan -> [ElaboratedPlanPackage])
-> ElaboratedInstallPlan
-> [Maybe (FilePath, Maybe FilePath)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedInstallPlan -> [ElaboratedPlanPackage]
forall ipkg srcpkg.
GenericInstallPlan ipkg srcpkg -> [GenericPlanPackage ipkg srcpkg]
InstallPlan.toList
dataDirEnvVarForPackage
:: DistDirLayout
-> ElaboratedConfiguredPackage
-> Maybe (String, Maybe FilePath)
dataDirEnvVarForPackage :: DistDirLayout
-> ElaboratedConfiguredPackage -> Maybe (FilePath, Maybe FilePath)
dataDirEnvVarForPackage DistDirLayout
distDirLayout ElaboratedConfiguredPackage
pkg =
case ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle ElaboratedConfiguredPackage
pkg of
BuildStyle
BuildAndInstall -> Maybe (FilePath, Maybe FilePath)
forall a. Maybe a
Nothing
BuildInplaceOnly{} ->
(FilePath, Maybe FilePath) -> Maybe (FilePath, Maybe FilePath)
forall a. a -> Maybe a
Just
( PackageDescription -> ShowS
pkgPathEnvVar (ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
pkg) FilePath
"datadir"
, FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$
PackageLocation (Maybe FilePath) -> FilePath
srcPath (ElaboratedConfiguredPackage -> PackageLocation (Maybe FilePath)
elabPkgSourceLocation ElaboratedConfiguredPackage
pkg)
FilePath -> ShowS
</> PackageDescription -> FilePath
dataDir (ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
pkg)
)
where
srcPath :: PackageLocation (Maybe FilePath) -> FilePath
srcPath (LocalUnpackedPackage FilePath
path) = FilePath
path
srcPath (LocalTarballPackage FilePath
_path) = FilePath
unpackedPath
srcPath (RemoteTarballPackage URI
_uri Maybe FilePath
_localTar) = FilePath
unpackedPath
srcPath (RepoTarballPackage Repo
_repo PackageIdentifier
_packageId Maybe FilePath
_localTar) = FilePath
unpackedPath
srcPath (RemoteSourceRepoPackage SourceRepoMaybe
_sourceRepo (Just FilePath
localCheckout)) = FilePath
localCheckout
srcPath (RemoteSourceRepoPackage SourceRepoMaybe
_sourceRepo Maybe FilePath
Nothing) =
ShowS
forall a. HasCallStack => FilePath -> a
error
FilePath
"calling dataDirEnvVarForPackage on a not-downloaded repo is an error"
unpackedPath :: FilePath
unpackedPath =
DistDirLayout -> PackageIdentifier -> FilePath
distUnpackedSrcDirectory DistDirLayout
distDirLayout (PackageIdentifier -> FilePath) -> PackageIdentifier -> FilePath
forall a b. (a -> b) -> a -> b
$ ElaboratedConfiguredPackage -> PackageIdentifier
elabPkgSourceId ElaboratedConfiguredPackage
pkg
instance Package ElaboratedConfiguredPackage where
packageId :: ElaboratedConfiguredPackage -> PackageIdentifier
packageId = ElaboratedConfiguredPackage -> PackageIdentifier
elabPkgSourceId
instance HasConfiguredId ElaboratedConfiguredPackage where
configuredId :: ElaboratedConfiguredPackage -> ConfiguredId
configuredId ElaboratedConfiguredPackage
elab =
PackageIdentifier
-> Maybe ComponentName -> ComponentId -> ConfiguredId
ConfiguredId (ElaboratedConfiguredPackage -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId ElaboratedConfiguredPackage
elab) (ElaboratedConfiguredPackage -> Maybe ComponentName
elabComponentName ElaboratedConfiguredPackage
elab) (ElaboratedConfiguredPackage -> ComponentId
elabComponentId ElaboratedConfiguredPackage
elab)
instance HasUnitId ElaboratedConfiguredPackage where
installedUnitId :: ElaboratedConfiguredPackage -> UnitId
installedUnitId = ElaboratedConfiguredPackage -> UnitId
elabUnitId
instance IsNode ElaboratedConfiguredPackage where
type Key ElaboratedConfiguredPackage = UnitId
nodeKey :: ElaboratedConfiguredPackage -> Key ElaboratedConfiguredPackage
nodeKey = ElaboratedConfiguredPackage -> UnitId
ElaboratedConfiguredPackage -> Key ElaboratedConfiguredPackage
elabUnitId
nodeNeighbors :: ElaboratedConfiguredPackage -> [Key ElaboratedConfiguredPackage]
nodeNeighbors = ElaboratedConfiguredPackage -> [UnitId]
ElaboratedConfiguredPackage -> [Key ElaboratedConfiguredPackage]
elabOrderDependencies
instance Binary ElaboratedConfiguredPackage
instance Structured ElaboratedConfiguredPackage
data ElaboratedPackageOrComponent
= ElabPackage ElaboratedPackage
| ElabComponent ElaboratedComponent
deriving (ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
(ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool)
-> (ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool)
-> Eq ElaboratedPackageOrComponent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
== :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
$c/= :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
/= :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
Eq, Int -> ElaboratedPackageOrComponent -> ShowS
[ElaboratedPackageOrComponent] -> ShowS
ElaboratedPackageOrComponent -> FilePath
(Int -> ElaboratedPackageOrComponent -> ShowS)
-> (ElaboratedPackageOrComponent -> FilePath)
-> ([ElaboratedPackageOrComponent] -> ShowS)
-> Show ElaboratedPackageOrComponent
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElaboratedPackageOrComponent -> ShowS
showsPrec :: Int -> ElaboratedPackageOrComponent -> ShowS
$cshow :: ElaboratedPackageOrComponent -> FilePath
show :: ElaboratedPackageOrComponent -> FilePath
$cshowList :: [ElaboratedPackageOrComponent] -> ShowS
showList :: [ElaboratedPackageOrComponent] -> ShowS
Show, (forall x.
ElaboratedPackageOrComponent -> Rep ElaboratedPackageOrComponent x)
-> (forall x.
Rep ElaboratedPackageOrComponent x -> ElaboratedPackageOrComponent)
-> Generic ElaboratedPackageOrComponent
forall x.
Rep ElaboratedPackageOrComponent x -> ElaboratedPackageOrComponent
forall x.
ElaboratedPackageOrComponent -> Rep ElaboratedPackageOrComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ElaboratedPackageOrComponent -> Rep ElaboratedPackageOrComponent x
from :: forall x.
ElaboratedPackageOrComponent -> Rep ElaboratedPackageOrComponent x
$cto :: forall x.
Rep ElaboratedPackageOrComponent x -> ElaboratedPackageOrComponent
to :: forall x.
Rep ElaboratedPackageOrComponent x -> ElaboratedPackageOrComponent
Generic)
instance Binary ElaboratedPackageOrComponent
instance Structured ElaboratedPackageOrComponent
elabComponentName :: ElaboratedConfiguredPackage -> Maybe ComponentName
elabComponentName :: ElaboratedConfiguredPackage -> Maybe ComponentName
elabComponentName ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
_ -> ComponentName -> Maybe ComponentName
forall a. a -> Maybe a
Just (ComponentName -> Maybe ComponentName)
-> ComponentName -> Maybe ComponentName
forall a b. (a -> b) -> a -> b
$ LibraryName -> ComponentName
CLibName LibraryName
LMainLibName
ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> Maybe ComponentName
compComponentName ElaboratedComponent
comp
elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> String
elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> FilePath
elabConfiguredName Verbosity
verbosity ElaboratedConfiguredPackage
elab
| Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
<= Verbosity
normal =
( case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
_ -> FilePath
""
ElabComponent ElaboratedComponent
comp ->
case ElaboratedComponent -> Maybe ComponentName
compComponentName ElaboratedComponent
comp of
Maybe ComponentName
Nothing -> FilePath
"setup from "
Just (CLibName LibraryName
LMainLibName) -> FilePath
""
Just ComponentName
cname -> ComponentName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow ComponentName
cname FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
" from "
)
FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ PackageIdentifier -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (ElaboratedConfiguredPackage -> PackageIdentifier
forall pkg. Package pkg => pkg -> PackageIdentifier
packageId ElaboratedConfiguredPackage
elab)
| Bool
otherwise =
UnitId -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (ElaboratedConfiguredPackage -> UnitId
elabUnitId ElaboratedConfiguredPackage
elab)
elabDistDirParams :: ElaboratedSharedConfig -> ElaboratedConfiguredPackage -> DistDirParams
elabDistDirParams :: ElaboratedSharedConfig
-> ElaboratedConfiguredPackage -> DistDirParams
elabDistDirParams ElaboratedSharedConfig
shared ElaboratedConfiguredPackage
elab =
DistDirParams
{ distParamUnitId :: UnitId
distParamUnitId = ElaboratedConfiguredPackage -> UnitId
forall pkg. HasUnitId pkg => pkg -> UnitId
installedUnitId ElaboratedConfiguredPackage
elab
, distParamComponentId :: ComponentId
distParamComponentId = ElaboratedConfiguredPackage -> ComponentId
elabComponentId ElaboratedConfiguredPackage
elab
, distParamPackageId :: PackageIdentifier
distParamPackageId = ElaboratedConfiguredPackage -> PackageIdentifier
elabPkgSourceId ElaboratedConfiguredPackage
elab
, distParamComponentName :: Maybe ComponentName
distParamComponentName = case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> Maybe ComponentName
compComponentName ElaboratedComponent
comp
ElabPackage ElaboratedPackage
_ -> Maybe ComponentName
forall a. Maybe a
Nothing
, distParamCompilerId :: CompilerId
distParamCompilerId = Compiler -> CompilerId
compilerId (ElaboratedSharedConfig -> Compiler
pkgConfigCompiler ElaboratedSharedConfig
shared)
, distParamPlatform :: Platform
distParamPlatform = ElaboratedSharedConfig -> Platform
pkgConfigPlatform ElaboratedSharedConfig
shared
, distParamOptimization :: OptimisationLevel
distParamOptimization = BuildOptions -> OptimisationLevel
LBC.withOptimization (BuildOptions -> OptimisationLevel)
-> BuildOptions -> OptimisationLevel
forall a b. (a -> b) -> a -> b
$ ElaboratedConfiguredPackage -> BuildOptions
elabBuildOptions ElaboratedConfiguredPackage
elab
}
elabOrderDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderDependencies ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
pkg -> [UnitId] -> [UnitId]
forall a. Ord a => [a] -> [a]
ordNub (ComponentDeps [UnitId] -> [UnitId]
forall a. Monoid a => ComponentDeps a -> a
CD.flatDeps (ElaboratedPackage -> ComponentDeps [UnitId]
pkgOrderDependencies ElaboratedPackage
pkg))
ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [UnitId]
compOrderDependencies ElaboratedComponent
comp
elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderLibDependencies ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
pkg ->
(ConfiguredId -> UnitId) -> [ConfiguredId] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId (ComponentId -> UnitId)
-> (ConfiguredId -> ComponentId) -> ConfiguredId -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId) ([ConfiguredId] -> [UnitId]) -> [ConfiguredId] -> [UnitId]
forall a b. (a -> b) -> a -> b
$
[ConfiguredId] -> [ConfiguredId]
forall a. Ord a => [a] -> [a]
ordNub ([ConfiguredId] -> [ConfiguredId])
-> [ConfiguredId] -> [ConfiguredId]
forall a b. (a -> b) -> a -> b
$
ComponentDeps [ConfiguredId] -> [ConfiguredId]
forall a. Monoid a => ComponentDeps a -> a
CD.flatDeps (((ConfiguredId, Bool) -> ConfiguredId)
-> [(ConfiguredId, Bool)] -> [ConfiguredId]
forall a b. (a -> b) -> [a] -> [b]
map (ConfiguredId, Bool) -> ConfiguredId
forall a b. (a, b) -> a
fst ([(ConfiguredId, Bool)] -> [ConfiguredId])
-> ComponentDeps [(ConfiguredId, Bool)]
-> ComponentDeps [ConfiguredId]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ElaboratedPackage -> ComponentDeps [(ConfiguredId, Bool)]
pkgLibDependencies ElaboratedPackage
pkg)
ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [UnitId]
compOrderLibDependencies ElaboratedComponent
comp
elabLibDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)]
elabLibDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)]
elabLibDependencies ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
pkg -> [(ConfiguredId, Bool)] -> [(ConfiguredId, Bool)]
forall a. Ord a => [a] -> [a]
ordNub (ComponentDeps [(ConfiguredId, Bool)] -> [(ConfiguredId, Bool)]
forall a. Monoid a => ComponentDeps a -> a
CD.nonSetupDeps (ElaboratedPackage -> ComponentDeps [(ConfiguredId, Bool)]
pkgLibDependencies ElaboratedPackage
pkg))
ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [(ConfiguredId, Bool)]
compLibDependencies ElaboratedComponent
comp
elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderExeDependencies =
(ComponentId -> UnitId) -> [ComponentId] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map ComponentId -> UnitId
newSimpleUnitId ([ComponentId] -> [UnitId])
-> (ElaboratedConfiguredPackage -> [ComponentId])
-> ElaboratedConfiguredPackage
-> [UnitId]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedConfiguredPackage -> [ComponentId]
elabExeDependencies
elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId]
elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId]
elabExeDependencies ElaboratedConfiguredPackage
elab = (ConfiguredId -> ComponentId) -> [ConfiguredId] -> [ComponentId]
forall a b. (a -> b) -> [a] -> [b]
map ConfiguredId -> ComponentId
confInstId ([ConfiguredId] -> [ComponentId])
-> [ConfiguredId] -> [ComponentId]
forall a b. (a -> b) -> a -> b
$
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
pkg -> ComponentDeps [ConfiguredId] -> [ConfiguredId]
forall a. Monoid a => ComponentDeps a -> a
CD.nonSetupDeps (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgExeDependencies ElaboratedPackage
pkg)
ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [ConfiguredId]
compExeDependencies ElaboratedComponent
comp
elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath]
elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath]
elabExeDependencyPaths ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
pkg -> ((ConfiguredId, FilePath) -> FilePath)
-> [(ConfiguredId, FilePath)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (ConfiguredId, FilePath) -> FilePath
forall a b. (a, b) -> b
snd ([(ConfiguredId, FilePath)] -> [FilePath])
-> [(ConfiguredId, FilePath)] -> [FilePath]
forall a b. (a -> b) -> a -> b
$ ComponentDeps [(ConfiguredId, FilePath)]
-> [(ConfiguredId, FilePath)]
forall a. Monoid a => ComponentDeps a -> a
CD.nonSetupDeps (ElaboratedPackage -> ComponentDeps [(ConfiguredId, FilePath)]
pkgExeDependencyPaths ElaboratedPackage
pkg)
ElabComponent ElaboratedComponent
comp -> ((ConfiguredId, FilePath) -> FilePath)
-> [(ConfiguredId, FilePath)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (ConfiguredId, FilePath) -> FilePath
forall a b. (a, b) -> b
snd (ElaboratedComponent -> [(ConfiguredId, FilePath)]
compExeDependencyPaths ElaboratedComponent
comp)
elabSetupDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)]
elabSetupDependencies :: ElaboratedConfiguredPackage -> [(ConfiguredId, Bool)]
elabSetupDependencies ElaboratedConfiguredPackage
elab =
case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
ElabPackage ElaboratedPackage
pkg -> ComponentDeps [(ConfiguredId, Bool)] -> [(ConfiguredId, Bool)]
forall a. Monoid a => ComponentDeps a -> a
CD.setupDeps (ElaboratedPackage -> ComponentDeps [(ConfiguredId, Bool)]
pkgLibDependencies ElaboratedPackage
pkg)
ElabComponent ElaboratedComponent
_ -> []
elabPkgConfigDependencies :: ElaboratedConfiguredPackage -> [(PkgconfigName, Maybe PkgconfigVersion)]
elabPkgConfigDependencies :: ElaboratedConfiguredPackage
-> [(PkgconfigName, Maybe PkgconfigVersion)]
elabPkgConfigDependencies ElaboratedConfiguredPackage{elabPkgOrComp :: ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp = ElabPackage ElaboratedPackage
pkg} =
ElaboratedPackage -> [(PkgconfigName, Maybe PkgconfigVersion)]
pkgPkgConfigDependencies ElaboratedPackage
pkg
elabPkgConfigDependencies ElaboratedConfiguredPackage{elabPkgOrComp :: ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp = ElabComponent ElaboratedComponent
comp} =
ElaboratedComponent -> [(PkgconfigName, Maybe PkgconfigVersion)]
compPkgConfigDependencies ElaboratedComponent
comp
elabInplaceDependencyBuildCacheFiles
:: DistDirLayout
-> ElaboratedSharedConfig
-> ElaboratedInstallPlan
-> ElaboratedConfiguredPackage
-> [FilePath]
elabInplaceDependencyBuildCacheFiles :: DistDirLayout
-> ElaboratedSharedConfig
-> ElaboratedInstallPlan
-> ElaboratedConfiguredPackage
-> [FilePath]
elabInplaceDependencyBuildCacheFiles DistDirLayout
layout ElaboratedSharedConfig
sconf ElaboratedInstallPlan
plan ElaboratedConfiguredPackage
root_elab =
ElaboratedPlanPackage -> [FilePath]
go (ElaboratedPlanPackage -> [FilePath])
-> [ElaboratedPlanPackage] -> [FilePath]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ElaboratedInstallPlan -> UnitId -> [ElaboratedPlanPackage]
forall ipkg srcpkg.
GenericInstallPlan ipkg srcpkg
-> UnitId -> [GenericPlanPackage ipkg srcpkg]
InstallPlan.directDeps ElaboratedInstallPlan
plan (ElaboratedConfiguredPackage -> Key ElaboratedConfiguredPackage
forall a. IsNode a => a -> Key a
nodeKey ElaboratedConfiguredPackage
root_elab)
where
go :: ElaboratedPlanPackage -> [FilePath]
go = (InstalledPackageInfo -> [FilePath])
-> (ElaboratedConfiguredPackage -> [FilePath])
-> ElaboratedPlanPackage
-> [FilePath]
forall ipkg a srcpkg.
(ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a
InstallPlan.foldPlanPackage ([FilePath] -> InstalledPackageInfo -> [FilePath]
forall a b. a -> b -> a
const []) ((ElaboratedConfiguredPackage -> [FilePath])
-> ElaboratedPlanPackage -> [FilePath])
-> (ElaboratedConfiguredPackage -> [FilePath])
-> ElaboratedPlanPackage
-> [FilePath]
forall a b. (a -> b) -> a -> b
$ \ElaboratedConfiguredPackage
elab -> do
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (BuildStyle -> Bool
isInplaceBuildStyle (ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle ElaboratedConfiguredPackage
elab))
FilePath -> [FilePath]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath -> [FilePath]) -> FilePath -> [FilePath]
forall a b. (a -> b) -> a -> b
$ DistDirLayout -> DistDirParams -> ShowS
distPackageCacheFile DistDirLayout
layout (ElaboratedSharedConfig
-> ElaboratedConfiguredPackage -> DistDirParams
elabDistDirParams ElaboratedSharedConfig
sconf ElaboratedConfiguredPackage
elab) FilePath
"build"
data ElaboratedComponent = ElaboratedComponent
{ ElaboratedComponent -> Component
compSolverName :: CD.Component
, ElaboratedComponent -> Maybe ComponentName
compComponentName :: Maybe ComponentName
, ElaboratedComponent -> [(ConfiguredId, Bool)]
compLibDependencies :: [(ConfiguredId, Bool)]
, ElaboratedComponent -> [OpenUnitId]
compLinkedLibDependencies :: [OpenUnitId]
, ElaboratedComponent -> [ConfiguredId]
compExeDependencies :: [ConfiguredId]
, ElaboratedComponent -> [(PkgconfigName, Maybe PkgconfigVersion)]
compPkgConfigDependencies :: [(PkgconfigName, Maybe PkgconfigVersion)]
, ElaboratedComponent -> [(ConfiguredId, FilePath)]
compExeDependencyPaths :: [(ConfiguredId, FilePath)]
, ElaboratedComponent -> [UnitId]
compOrderLibDependencies :: [UnitId]
}
deriving (ElaboratedComponent -> ElaboratedComponent -> Bool
(ElaboratedComponent -> ElaboratedComponent -> Bool)
-> (ElaboratedComponent -> ElaboratedComponent -> Bool)
-> Eq ElaboratedComponent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElaboratedComponent -> ElaboratedComponent -> Bool
== :: ElaboratedComponent -> ElaboratedComponent -> Bool
$c/= :: ElaboratedComponent -> ElaboratedComponent -> Bool
/= :: ElaboratedComponent -> ElaboratedComponent -> Bool
Eq, Int -> ElaboratedComponent -> ShowS
[ElaboratedComponent] -> ShowS
ElaboratedComponent -> FilePath
(Int -> ElaboratedComponent -> ShowS)
-> (ElaboratedComponent -> FilePath)
-> ([ElaboratedComponent] -> ShowS)
-> Show ElaboratedComponent
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElaboratedComponent -> ShowS
showsPrec :: Int -> ElaboratedComponent -> ShowS
$cshow :: ElaboratedComponent -> FilePath
show :: ElaboratedComponent -> FilePath
$cshowList :: [ElaboratedComponent] -> ShowS
showList :: [ElaboratedComponent] -> ShowS
Show, (forall x. ElaboratedComponent -> Rep ElaboratedComponent x)
-> (forall x. Rep ElaboratedComponent x -> ElaboratedComponent)
-> Generic ElaboratedComponent
forall x. Rep ElaboratedComponent x -> ElaboratedComponent
forall x. ElaboratedComponent -> Rep ElaboratedComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ElaboratedComponent -> Rep ElaboratedComponent x
from :: forall x. ElaboratedComponent -> Rep ElaboratedComponent x
$cto :: forall x. Rep ElaboratedComponent x -> ElaboratedComponent
to :: forall x. Rep ElaboratedComponent x -> ElaboratedComponent
Generic)
instance Binary ElaboratedComponent
instance Structured ElaboratedComponent
compOrderDependencies :: ElaboratedComponent -> [UnitId]
compOrderDependencies :: ElaboratedComponent -> [UnitId]
compOrderDependencies ElaboratedComponent
comp =
ElaboratedComponent -> [UnitId]
compOrderLibDependencies ElaboratedComponent
comp
[UnitId] -> [UnitId] -> [UnitId]
forall a. [a] -> [a] -> [a]
++ ElaboratedComponent -> [UnitId]
compOrderExeDependencies ElaboratedComponent
comp
compOrderExeDependencies :: ElaboratedComponent -> [UnitId]
compOrderExeDependencies :: ElaboratedComponent -> [UnitId]
compOrderExeDependencies = (ConfiguredId -> UnitId) -> [ConfiguredId] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId (ComponentId -> UnitId)
-> (ConfiguredId -> ComponentId) -> ConfiguredId -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId) ([ConfiguredId] -> [UnitId])
-> (ElaboratedComponent -> [ConfiguredId])
-> ElaboratedComponent
-> [UnitId]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedComponent -> [ConfiguredId]
compExeDependencies
data ElaboratedPackage = ElaboratedPackage
{ ElaboratedPackage -> ComponentId
pkgInstalledId :: InstalledPackageId
, ElaboratedPackage -> ComponentDeps [(ConfiguredId, Bool)]
pkgLibDependencies :: ComponentDeps [(ConfiguredId, Bool)]
, ElaboratedPackage -> ComponentDeps [()]
pkgDependsOnSelfLib :: ComponentDeps [()]
, ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgExeDependencies :: ComponentDeps [ConfiguredId]
, ElaboratedPackage -> ComponentDeps [(ConfiguredId, FilePath)]
pkgExeDependencyPaths :: ComponentDeps [(ConfiguredId, FilePath)]
, ElaboratedPackage -> [(PkgconfigName, Maybe PkgconfigVersion)]
pkgPkgConfigDependencies :: [(PkgconfigName, Maybe PkgconfigVersion)]
, ElaboratedPackage -> OptionalStanzaSet
pkgStanzasEnabled :: OptionalStanzaSet
, ElaboratedPackage -> NonEmpty NotPerComponentReason
pkgWhyNotPerComponent :: NE.NonEmpty NotPerComponentReason
}
deriving (ElaboratedPackage -> ElaboratedPackage -> Bool
(ElaboratedPackage -> ElaboratedPackage -> Bool)
-> (ElaboratedPackage -> ElaboratedPackage -> Bool)
-> Eq ElaboratedPackage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ElaboratedPackage -> ElaboratedPackage -> Bool
== :: ElaboratedPackage -> ElaboratedPackage -> Bool
$c/= :: ElaboratedPackage -> ElaboratedPackage -> Bool
/= :: ElaboratedPackage -> ElaboratedPackage -> Bool
Eq, Int -> ElaboratedPackage -> ShowS
[ElaboratedPackage] -> ShowS
ElaboratedPackage -> FilePath
(Int -> ElaboratedPackage -> ShowS)
-> (ElaboratedPackage -> FilePath)
-> ([ElaboratedPackage] -> ShowS)
-> Show ElaboratedPackage
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ElaboratedPackage -> ShowS
showsPrec :: Int -> ElaboratedPackage -> ShowS
$cshow :: ElaboratedPackage -> FilePath
show :: ElaboratedPackage -> FilePath
$cshowList :: [ElaboratedPackage] -> ShowS
showList :: [ElaboratedPackage] -> ShowS
Show, (forall x. ElaboratedPackage -> Rep ElaboratedPackage x)
-> (forall x. Rep ElaboratedPackage x -> ElaboratedPackage)
-> Generic ElaboratedPackage
forall x. Rep ElaboratedPackage x -> ElaboratedPackage
forall x. ElaboratedPackage -> Rep ElaboratedPackage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ElaboratedPackage -> Rep ElaboratedPackage x
from :: forall x. ElaboratedPackage -> Rep ElaboratedPackage x
$cto :: forall x. Rep ElaboratedPackage x -> ElaboratedPackage
to :: forall x. Rep ElaboratedPackage x -> ElaboratedPackage
Generic)
instance Binary ElaboratedPackage
instance Structured ElaboratedPackage
data NotPerComponentReason
=
CuzBuildType !NotPerComponentBuildType
|
CuzCabalSpecVersion
|
CuzNoBuildableComponents
|
CuzDisablePerComponent
deriving (NotPerComponentReason -> NotPerComponentReason -> Bool
(NotPerComponentReason -> NotPerComponentReason -> Bool)
-> (NotPerComponentReason -> NotPerComponentReason -> Bool)
-> Eq NotPerComponentReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NotPerComponentReason -> NotPerComponentReason -> Bool
== :: NotPerComponentReason -> NotPerComponentReason -> Bool
$c/= :: NotPerComponentReason -> NotPerComponentReason -> Bool
/= :: NotPerComponentReason -> NotPerComponentReason -> Bool
Eq, Int -> NotPerComponentReason -> ShowS
[NotPerComponentReason] -> ShowS
NotPerComponentReason -> FilePath
(Int -> NotPerComponentReason -> ShowS)
-> (NotPerComponentReason -> FilePath)
-> ([NotPerComponentReason] -> ShowS)
-> Show NotPerComponentReason
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NotPerComponentReason -> ShowS
showsPrec :: Int -> NotPerComponentReason -> ShowS
$cshow :: NotPerComponentReason -> FilePath
show :: NotPerComponentReason -> FilePath
$cshowList :: [NotPerComponentReason] -> ShowS
showList :: [NotPerComponentReason] -> ShowS
Show, (forall x. NotPerComponentReason -> Rep NotPerComponentReason x)
-> (forall x. Rep NotPerComponentReason x -> NotPerComponentReason)
-> Generic NotPerComponentReason
forall x. Rep NotPerComponentReason x -> NotPerComponentReason
forall x. NotPerComponentReason -> Rep NotPerComponentReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NotPerComponentReason -> Rep NotPerComponentReason x
from :: forall x. NotPerComponentReason -> Rep NotPerComponentReason x
$cto :: forall x. Rep NotPerComponentReason x -> NotPerComponentReason
to :: forall x. Rep NotPerComponentReason x -> NotPerComponentReason
Generic)
data NotPerComponentBuildType
= CuzConfigureBuildType
| CuzCustomBuildType
| CuzMakeBuildType
deriving (NotPerComponentBuildType -> NotPerComponentBuildType -> Bool
(NotPerComponentBuildType -> NotPerComponentBuildType -> Bool)
-> (NotPerComponentBuildType -> NotPerComponentBuildType -> Bool)
-> Eq NotPerComponentBuildType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NotPerComponentBuildType -> NotPerComponentBuildType -> Bool
== :: NotPerComponentBuildType -> NotPerComponentBuildType -> Bool
$c/= :: NotPerComponentBuildType -> NotPerComponentBuildType -> Bool
/= :: NotPerComponentBuildType -> NotPerComponentBuildType -> Bool
Eq, Int -> NotPerComponentBuildType -> ShowS
[NotPerComponentBuildType] -> ShowS
NotPerComponentBuildType -> FilePath
(Int -> NotPerComponentBuildType -> ShowS)
-> (NotPerComponentBuildType -> FilePath)
-> ([NotPerComponentBuildType] -> ShowS)
-> Show NotPerComponentBuildType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NotPerComponentBuildType -> ShowS
showsPrec :: Int -> NotPerComponentBuildType -> ShowS
$cshow :: NotPerComponentBuildType -> FilePath
show :: NotPerComponentBuildType -> FilePath
$cshowList :: [NotPerComponentBuildType] -> ShowS
showList :: [NotPerComponentBuildType] -> ShowS
Show, (forall x.
NotPerComponentBuildType -> Rep NotPerComponentBuildType x)
-> (forall x.
Rep NotPerComponentBuildType x -> NotPerComponentBuildType)
-> Generic NotPerComponentBuildType
forall x.
Rep NotPerComponentBuildType x -> NotPerComponentBuildType
forall x.
NotPerComponentBuildType -> Rep NotPerComponentBuildType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
NotPerComponentBuildType -> Rep NotPerComponentBuildType x
from :: forall x.
NotPerComponentBuildType -> Rep NotPerComponentBuildType x
$cto :: forall x.
Rep NotPerComponentBuildType x -> NotPerComponentBuildType
to :: forall x.
Rep NotPerComponentBuildType x -> NotPerComponentBuildType
Generic)
instance Binary NotPerComponentBuildType
instance Structured NotPerComponentBuildType
instance Binary NotPerComponentReason
instance Structured NotPerComponentReason
whyNotPerComponent :: NotPerComponentReason -> String
whyNotPerComponent :: NotPerComponentReason -> FilePath
whyNotPerComponent = \case
CuzBuildType NotPerComponentBuildType
bt ->
FilePath
"build-type is " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ case NotPerComponentBuildType
bt of
NotPerComponentBuildType
CuzConfigureBuildType -> FilePath
"Configure"
NotPerComponentBuildType
CuzCustomBuildType -> FilePath
"Custom"
NotPerComponentBuildType
CuzMakeBuildType -> FilePath
"Make"
NotPerComponentReason
CuzCabalSpecVersion -> FilePath
"cabal-version is less than 1.8"
NotPerComponentReason
CuzNoBuildableComponents -> FilePath
"there are no buildable components"
NotPerComponentReason
CuzDisablePerComponent -> FilePath
"you passed --disable-per-component"
pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId]
pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId]
pkgOrderDependencies ElaboratedPackage
pkg =
([ConfiguredId] -> [UnitId])
-> ComponentDeps [ConfiguredId] -> ComponentDeps [UnitId]
forall a b. (a -> b) -> ComponentDeps a -> ComponentDeps b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ConfiguredId -> UnitId) -> [ConfiguredId] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId (ComponentId -> UnitId)
-> (ConfiguredId -> ComponentId) -> ConfiguredId -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId)) (((ConfiguredId, Bool) -> ConfiguredId)
-> [(ConfiguredId, Bool)] -> [ConfiguredId]
forall a b. (a -> b) -> [a] -> [b]
map (ConfiguredId, Bool) -> ConfiguredId
forall a b. (a, b) -> a
fst ([(ConfiguredId, Bool)] -> [ConfiguredId])
-> ComponentDeps [(ConfiguredId, Bool)]
-> ComponentDeps [ConfiguredId]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ElaboratedPackage -> ComponentDeps [(ConfiguredId, Bool)]
pkgLibDependencies ElaboratedPackage
pkg)
ComponentDeps [UnitId]
-> ComponentDeps [UnitId] -> ComponentDeps [UnitId]
forall a. Monoid a => a -> a -> a
`Mon.mappend` ([ConfiguredId] -> [UnitId])
-> ComponentDeps [ConfiguredId] -> ComponentDeps [UnitId]
forall a b. (a -> b) -> ComponentDeps a -> ComponentDeps b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ConfiguredId -> UnitId) -> [ConfiguredId] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId (ComponentId -> UnitId)
-> (ConfiguredId -> ComponentId) -> ConfiguredId -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId)) (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgExeDependencies ElaboratedPackage
pkg)
data BuildStyle
=
BuildAndInstall
|
BuildInplaceOnly MemoryOrDisk
deriving (BuildStyle -> BuildStyle -> Bool
(BuildStyle -> BuildStyle -> Bool)
-> (BuildStyle -> BuildStyle -> Bool) -> Eq BuildStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BuildStyle -> BuildStyle -> Bool
== :: BuildStyle -> BuildStyle -> Bool
$c/= :: BuildStyle -> BuildStyle -> Bool
/= :: BuildStyle -> BuildStyle -> Bool
Eq, Eq BuildStyle
Eq BuildStyle =>
(BuildStyle -> BuildStyle -> Ordering)
-> (BuildStyle -> BuildStyle -> Bool)
-> (BuildStyle -> BuildStyle -> Bool)
-> (BuildStyle -> BuildStyle -> Bool)
-> (BuildStyle -> BuildStyle -> Bool)
-> (BuildStyle -> BuildStyle -> BuildStyle)
-> (BuildStyle -> BuildStyle -> BuildStyle)
-> Ord BuildStyle
BuildStyle -> BuildStyle -> Bool
BuildStyle -> BuildStyle -> Ordering
BuildStyle -> BuildStyle -> BuildStyle
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BuildStyle -> BuildStyle -> Ordering
compare :: BuildStyle -> BuildStyle -> Ordering
$c< :: BuildStyle -> BuildStyle -> Bool
< :: BuildStyle -> BuildStyle -> Bool
$c<= :: BuildStyle -> BuildStyle -> Bool
<= :: BuildStyle -> BuildStyle -> Bool
$c> :: BuildStyle -> BuildStyle -> Bool
> :: BuildStyle -> BuildStyle -> Bool
$c>= :: BuildStyle -> BuildStyle -> Bool
>= :: BuildStyle -> BuildStyle -> Bool
$cmax :: BuildStyle -> BuildStyle -> BuildStyle
max :: BuildStyle -> BuildStyle -> BuildStyle
$cmin :: BuildStyle -> BuildStyle -> BuildStyle
min :: BuildStyle -> BuildStyle -> BuildStyle
Ord, Int -> BuildStyle -> ShowS
[BuildStyle] -> ShowS
BuildStyle -> FilePath
(Int -> BuildStyle -> ShowS)
-> (BuildStyle -> FilePath)
-> ([BuildStyle] -> ShowS)
-> Show BuildStyle
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BuildStyle -> ShowS
showsPrec :: Int -> BuildStyle -> ShowS
$cshow :: BuildStyle -> FilePath
show :: BuildStyle -> FilePath
$cshowList :: [BuildStyle] -> ShowS
showList :: [BuildStyle] -> ShowS
Show, (forall x. BuildStyle -> Rep BuildStyle x)
-> (forall x. Rep BuildStyle x -> BuildStyle) -> Generic BuildStyle
forall x. Rep BuildStyle x -> BuildStyle
forall x. BuildStyle -> Rep BuildStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BuildStyle -> Rep BuildStyle x
from :: forall x. BuildStyle -> Rep BuildStyle x
$cto :: forall x. Rep BuildStyle x -> BuildStyle
to :: forall x. Rep BuildStyle x -> BuildStyle
Generic)
data MemoryOrDisk
= OnDisk
| InMemory
deriving (MemoryOrDisk -> MemoryOrDisk -> Bool
(MemoryOrDisk -> MemoryOrDisk -> Bool)
-> (MemoryOrDisk -> MemoryOrDisk -> Bool) -> Eq MemoryOrDisk
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemoryOrDisk -> MemoryOrDisk -> Bool
== :: MemoryOrDisk -> MemoryOrDisk -> Bool
$c/= :: MemoryOrDisk -> MemoryOrDisk -> Bool
/= :: MemoryOrDisk -> MemoryOrDisk -> Bool
Eq, Eq MemoryOrDisk
Eq MemoryOrDisk =>
(MemoryOrDisk -> MemoryOrDisk -> Ordering)
-> (MemoryOrDisk -> MemoryOrDisk -> Bool)
-> (MemoryOrDisk -> MemoryOrDisk -> Bool)
-> (MemoryOrDisk -> MemoryOrDisk -> Bool)
-> (MemoryOrDisk -> MemoryOrDisk -> Bool)
-> (MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk)
-> (MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk)
-> Ord MemoryOrDisk
MemoryOrDisk -> MemoryOrDisk -> Bool
MemoryOrDisk -> MemoryOrDisk -> Ordering
MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MemoryOrDisk -> MemoryOrDisk -> Ordering
compare :: MemoryOrDisk -> MemoryOrDisk -> Ordering
$c< :: MemoryOrDisk -> MemoryOrDisk -> Bool
< :: MemoryOrDisk -> MemoryOrDisk -> Bool
$c<= :: MemoryOrDisk -> MemoryOrDisk -> Bool
<= :: MemoryOrDisk -> MemoryOrDisk -> Bool
$c> :: MemoryOrDisk -> MemoryOrDisk -> Bool
> :: MemoryOrDisk -> MemoryOrDisk -> Bool
$c>= :: MemoryOrDisk -> MemoryOrDisk -> Bool
>= :: MemoryOrDisk -> MemoryOrDisk -> Bool
$cmax :: MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk
max :: MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk
$cmin :: MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk
min :: MemoryOrDisk -> MemoryOrDisk -> MemoryOrDisk
Ord, Int -> MemoryOrDisk -> ShowS
[MemoryOrDisk] -> ShowS
MemoryOrDisk -> FilePath
(Int -> MemoryOrDisk -> ShowS)
-> (MemoryOrDisk -> FilePath)
-> ([MemoryOrDisk] -> ShowS)
-> Show MemoryOrDisk
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MemoryOrDisk -> ShowS
showsPrec :: Int -> MemoryOrDisk -> ShowS
$cshow :: MemoryOrDisk -> FilePath
show :: MemoryOrDisk -> FilePath
$cshowList :: [MemoryOrDisk] -> ShowS
showList :: [MemoryOrDisk] -> ShowS
Show, (forall x. MemoryOrDisk -> Rep MemoryOrDisk x)
-> (forall x. Rep MemoryOrDisk x -> MemoryOrDisk)
-> Generic MemoryOrDisk
forall x. Rep MemoryOrDisk x -> MemoryOrDisk
forall x. MemoryOrDisk -> Rep MemoryOrDisk x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MemoryOrDisk -> Rep MemoryOrDisk x
from :: forall x. MemoryOrDisk -> Rep MemoryOrDisk x
$cto :: forall x. Rep MemoryOrDisk x -> MemoryOrDisk
to :: forall x. Rep MemoryOrDisk x -> MemoryOrDisk
Generic)
isInplaceBuildStyle :: BuildStyle -> Bool
isInplaceBuildStyle :: BuildStyle -> Bool
isInplaceBuildStyle (BuildInplaceOnly{}) = Bool
True
isInplaceBuildStyle BuildStyle
BuildAndInstall = Bool
False
instance Binary MemoryOrDisk
instance Structured MemoryOrDisk
instance Semigroup BuildStyle where
<> :: BuildStyle -> BuildStyle -> BuildStyle
(<>) = BuildStyle -> BuildStyle -> BuildStyle
forall a. Ord a => a -> a -> a
max
instance Monoid BuildStyle where
mempty :: BuildStyle
mempty = BuildStyle
BuildAndInstall
instance Binary BuildStyle
instance Structured BuildStyle
type CabalFileText = LBS.ByteString
type ElaboratedReadyPackage = GenericReadyPackage ElaboratedConfiguredPackage
data ComponentTarget = ComponentTarget ComponentName SubComponentTarget
deriving (ComponentTarget -> ComponentTarget -> Bool
(ComponentTarget -> ComponentTarget -> Bool)
-> (ComponentTarget -> ComponentTarget -> Bool)
-> Eq ComponentTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComponentTarget -> ComponentTarget -> Bool
== :: ComponentTarget -> ComponentTarget -> Bool
$c/= :: ComponentTarget -> ComponentTarget -> Bool
/= :: ComponentTarget -> ComponentTarget -> Bool
Eq, Eq ComponentTarget
Eq ComponentTarget =>
(ComponentTarget -> ComponentTarget -> Ordering)
-> (ComponentTarget -> ComponentTarget -> Bool)
-> (ComponentTarget -> ComponentTarget -> Bool)
-> (ComponentTarget -> ComponentTarget -> Bool)
-> (ComponentTarget -> ComponentTarget -> Bool)
-> (ComponentTarget -> ComponentTarget -> ComponentTarget)
-> (ComponentTarget -> ComponentTarget -> ComponentTarget)
-> Ord ComponentTarget
ComponentTarget -> ComponentTarget -> Bool
ComponentTarget -> ComponentTarget -> Ordering
ComponentTarget -> ComponentTarget -> ComponentTarget
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ComponentTarget -> ComponentTarget -> Ordering
compare :: ComponentTarget -> ComponentTarget -> Ordering
$c< :: ComponentTarget -> ComponentTarget -> Bool
< :: ComponentTarget -> ComponentTarget -> Bool
$c<= :: ComponentTarget -> ComponentTarget -> Bool
<= :: ComponentTarget -> ComponentTarget -> Bool
$c> :: ComponentTarget -> ComponentTarget -> Bool
> :: ComponentTarget -> ComponentTarget -> Bool
$c>= :: ComponentTarget -> ComponentTarget -> Bool
>= :: ComponentTarget -> ComponentTarget -> Bool
$cmax :: ComponentTarget -> ComponentTarget -> ComponentTarget
max :: ComponentTarget -> ComponentTarget -> ComponentTarget
$cmin :: ComponentTarget -> ComponentTarget -> ComponentTarget
min :: ComponentTarget -> ComponentTarget -> ComponentTarget
Ord, Int -> ComponentTarget -> ShowS
[ComponentTarget] -> ShowS
ComponentTarget -> FilePath
(Int -> ComponentTarget -> ShowS)
-> (ComponentTarget -> FilePath)
-> ([ComponentTarget] -> ShowS)
-> Show ComponentTarget
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentTarget -> ShowS
showsPrec :: Int -> ComponentTarget -> ShowS
$cshow :: ComponentTarget -> FilePath
show :: ComponentTarget -> FilePath
$cshowList :: [ComponentTarget] -> ShowS
showList :: [ComponentTarget] -> ShowS
Show, (forall x. ComponentTarget -> Rep ComponentTarget x)
-> (forall x. Rep ComponentTarget x -> ComponentTarget)
-> Generic ComponentTarget
forall x. Rep ComponentTarget x -> ComponentTarget
forall x. ComponentTarget -> Rep ComponentTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ComponentTarget -> Rep ComponentTarget x
from :: forall x. ComponentTarget -> Rep ComponentTarget x
$cto :: forall x. Rep ComponentTarget x -> ComponentTarget
to :: forall x. Rep ComponentTarget x -> ComponentTarget
Generic)
instance Binary ComponentTarget
instance Structured ComponentTarget
showComponentTarget :: PackageId -> ComponentTarget -> String
showComponentTarget :: PackageIdentifier -> ComponentTarget -> FilePath
showComponentTarget PackageIdentifier
pkgid =
PackageIdentifier -> BuildTarget -> FilePath
Cabal.showBuildTarget PackageIdentifier
pkgid (BuildTarget -> FilePath)
-> (ComponentTarget -> BuildTarget) -> ComponentTarget -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComponentTarget -> BuildTarget
toBuildTarget
where
toBuildTarget :: ComponentTarget -> Cabal.BuildTarget
toBuildTarget :: ComponentTarget -> BuildTarget
toBuildTarget (ComponentTarget ComponentName
cname SubComponentTarget
subtarget) =
case SubComponentTarget
subtarget of
SubComponentTarget
WholeComponent -> ComponentName -> BuildTarget
Cabal.BuildTargetComponent ComponentName
cname
ModuleTarget ModuleName
mname -> ComponentName -> ModuleName -> BuildTarget
Cabal.BuildTargetModule ComponentName
cname ModuleName
mname
FileTarget FilePath
fname -> ComponentName -> FilePath -> BuildTarget
Cabal.BuildTargetFile ComponentName
cname FilePath
fname
showTestComponentTarget :: PackageId -> ComponentTarget -> Maybe String
showTestComponentTarget :: PackageIdentifier -> ComponentTarget -> Maybe FilePath
showTestComponentTarget PackageIdentifier
_ (ComponentTarget (CTestName UnqualComponentName
n) SubComponentTarget
_) = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow UnqualComponentName
n
showTestComponentTarget PackageIdentifier
_ ComponentTarget
_ = Maybe FilePath
forall a. Maybe a
Nothing
isTestComponentTarget :: ComponentTarget -> Bool
isTestComponentTarget :: ComponentTarget -> Bool
isTestComponentTarget (ComponentTarget (CTestName UnqualComponentName
_) SubComponentTarget
_) = Bool
True
isTestComponentTarget ComponentTarget
_ = Bool
False
showBenchComponentTarget :: PackageId -> ComponentTarget -> Maybe String
showBenchComponentTarget :: PackageIdentifier -> ComponentTarget -> Maybe FilePath
showBenchComponentTarget PackageIdentifier
_ (ComponentTarget (CBenchName UnqualComponentName
n) SubComponentTarget
_) = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath) -> FilePath -> Maybe FilePath
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow UnqualComponentName
n
showBenchComponentTarget PackageIdentifier
_ ComponentTarget
_ = Maybe FilePath
forall a. Maybe a
Nothing
isBenchComponentTarget :: ComponentTarget -> Bool
isBenchComponentTarget :: ComponentTarget -> Bool
isBenchComponentTarget (ComponentTarget (CBenchName UnqualComponentName
_) SubComponentTarget
_) = Bool
True
isBenchComponentTarget ComponentTarget
_ = Bool
False
isForeignLibComponentTarget :: ComponentTarget -> Bool
isForeignLibComponentTarget :: ComponentTarget -> Bool
isForeignLibComponentTarget (ComponentTarget (CFLibName UnqualComponentName
_) SubComponentTarget
_) = Bool
True
isForeignLibComponentTarget ComponentTarget
_ = Bool
False
isExeComponentTarget :: ComponentTarget -> Bool
isExeComponentTarget :: ComponentTarget -> Bool
isExeComponentTarget (ComponentTarget (CExeName UnqualComponentName
_) SubComponentTarget
_) = Bool
True
isExeComponentTarget ComponentTarget
_ = Bool
False
isSubLibComponentTarget :: ComponentTarget -> Bool
isSubLibComponentTarget :: ComponentTarget -> Bool
isSubLibComponentTarget (ComponentTarget (CLibName (LSubLibName UnqualComponentName
_)) SubComponentTarget
_) = Bool
True
isSubLibComponentTarget ComponentTarget
_ = Bool
False
componentOptionalStanza :: CD.Component -> Maybe OptionalStanza
componentOptionalStanza :: Component -> Maybe OptionalStanza
componentOptionalStanza (CD.ComponentTest UnqualComponentName
_) = OptionalStanza -> Maybe OptionalStanza
forall a. a -> Maybe a
Just OptionalStanza
TestStanzas
componentOptionalStanza (CD.ComponentBench UnqualComponentName
_) = OptionalStanza -> Maybe OptionalStanza
forall a. a -> Maybe a
Just OptionalStanza
BenchStanzas
componentOptionalStanza Component
_ = Maybe OptionalStanza
forall a. Maybe a
Nothing
data SetupScriptStyle
= SetupCustomExplicitDeps
| SetupCustomImplicitDeps
| SetupNonCustomExternalLib
| SetupNonCustomInternalLib
deriving (SetupScriptStyle -> SetupScriptStyle -> Bool
(SetupScriptStyle -> SetupScriptStyle -> Bool)
-> (SetupScriptStyle -> SetupScriptStyle -> Bool)
-> Eq SetupScriptStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetupScriptStyle -> SetupScriptStyle -> Bool
== :: SetupScriptStyle -> SetupScriptStyle -> Bool
$c/= :: SetupScriptStyle -> SetupScriptStyle -> Bool
/= :: SetupScriptStyle -> SetupScriptStyle -> Bool
Eq, Int -> SetupScriptStyle -> ShowS
[SetupScriptStyle] -> ShowS
SetupScriptStyle -> FilePath
(Int -> SetupScriptStyle -> ShowS)
-> (SetupScriptStyle -> FilePath)
-> ([SetupScriptStyle] -> ShowS)
-> Show SetupScriptStyle
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetupScriptStyle -> ShowS
showsPrec :: Int -> SetupScriptStyle -> ShowS
$cshow :: SetupScriptStyle -> FilePath
show :: SetupScriptStyle -> FilePath
$cshowList :: [SetupScriptStyle] -> ShowS
showList :: [SetupScriptStyle] -> ShowS
Show, (forall x. SetupScriptStyle -> Rep SetupScriptStyle x)
-> (forall x. Rep SetupScriptStyle x -> SetupScriptStyle)
-> Generic SetupScriptStyle
forall x. Rep SetupScriptStyle x -> SetupScriptStyle
forall x. SetupScriptStyle -> Rep SetupScriptStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SetupScriptStyle -> Rep SetupScriptStyle x
from :: forall x. SetupScriptStyle -> Rep SetupScriptStyle x
$cto :: forall x. Rep SetupScriptStyle x -> SetupScriptStyle
to :: forall x. Rep SetupScriptStyle x -> SetupScriptStyle
Generic, Typeable)
instance Binary SetupScriptStyle
instance Structured SetupScriptStyle