{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TypeFamilies #-}

-- | Types used while planning how to build everything in a project.
--
-- Primarily this is the 'ElaboratedInstallPlan'.
--
module Distribution.Client.ProjectPlanning.Types (
    SolverInstallPlan,

    -- * Elaborated install plan types
    ElaboratedInstallPlan,
    normaliseConfiguredPackage,
    ElaboratedConfiguredPackage(..),

    elabDistDirParams,
    elabExeDependencyPaths,
    elabLibDependencies,
    elabOrderLibDependencies,
    elabExeDependencies,
    elabOrderExeDependencies,
    elabSetupDependencies,
    elabPkgConfigDependencies,
    elabInplaceDependencyBuildCacheFiles,
    elabRequiresRegistration,
    dataDirsEnvironmentForPlan,

    elabPlanPackageName,
    elabConfiguredName,
    elabComponentName,

    ElaboratedPackageOrComponent(..),
    ElaboratedComponent(..),
    ElaboratedPackage(..),
    pkgOrderDependencies,
    ElaboratedPlanPackage,
    ElaboratedSharedConfig(..),
    ElaboratedReadyPackage,
    BuildStyle(..),
    CabalFileText,

    -- * Build targets
    ComponentTarget(..),
    showComponentTarget,
    showTestComponentTarget,
    showBenchComponentTarget,
    SubComponentTarget(..),

    isSubLibComponentTarget,
    isForeignLibComponentTarget,
    isExeComponentTarget,
    isTestComponentTarget,
    isBenchComponentTarget,

    componentOptionalStanza,

    -- * Setup script
    SetupScriptStyle(..),
  ) where

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

import           Distribution.Client.TargetSelector
                   ( SubComponentTarget(..) )
import           Distribution.Client.PackageHash

import           Distribution.Client.Types
import qualified Distribution.Client.InstallPlan as InstallPlan
import           Distribution.Client.InstallPlan
                   ( GenericInstallPlan, GenericPlanPackage(..) )
import           Distribution.Client.SolverInstallPlan
                   ( SolverInstallPlan )
import           Distribution.Client.DistDirLayout

import           Distribution.Backpack
import           Distribution.Backpack.ModuleShape

import           Distribution.Verbosity (normal)
import           Distribution.Types.ComponentRequestedSpec
import           Distribution.Types.PkgconfigVersion
import           Distribution.Types.PackageDescription (PackageDescription(..))
import           Distribution.Package
import           Distribution.System
import qualified Distribution.PackageDescription as Cabal
import           Distribution.InstalledPackageInfo (InstalledPackageInfo)
import           Distribution.Simple.Compiler
import           Distribution.Simple.Build.PathsModule (pkgPathEnvVar)
import qualified Distribution.Simple.BuildTarget as Cabal
import           Distribution.Simple.Program
import           Distribution.ModuleName (ModuleName)
import           Distribution.Simple.LocalBuildInfo
                   ( ComponentName(..), LibraryName(..) )
import qualified Distribution.Simple.InstallDirs as InstallDirs
import           Distribution.Simple.InstallDirs (PathTemplate)
import           Distribution.Simple.Setup
                   ( HaddockTarget, TestShowDetails, DumpBuildInfo (..), ReplOptions )
import           Distribution.Version

import qualified Distribution.Solver.Types.ComponentDeps as CD
import           Distribution.Solver.Types.ComponentDeps (ComponentDeps)
import           Distribution.Solver.Types.OptionalStanza
import           Distribution.Compat.Graph (IsNode(..))
import           Distribution.Simple.Utils (ordNub)

import qualified Data.Map as Map
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Monoid as Mon
import           System.FilePath ((</>))


-- | The combination of an elaborated install plan plus a
-- 'ElaboratedSharedConfig' contains all the details necessary to be able
-- to execute the plan without having to make further policy decisions.
--
-- It does not include dynamic elements such as resources (such as http
-- connections).
--
type ElaboratedInstallPlan
   = GenericInstallPlan InstalledPackageInfo
                        ElaboratedConfiguredPackage

type ElaboratedPlanPackage
   = GenericPlanPackage InstalledPackageInfo
                        ElaboratedConfiguredPackage

-- | User-friendly display string for an 'ElaboratedPlanPackage'.
elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> String
elabPlanPackageName :: Verbosity -> ElaboratedPlanPackage -> FilePath
elabPlanPackageName Verbosity
verbosity (PreExisting InstalledPackageInfo
ipkg)
    | Verbosity
verbosity forall a. Ord a => a -> a -> Bool
<= Verbosity
normal = forall a. Pretty a => a -> FilePath
prettyShow (forall pkg. Package pkg => pkg -> PackageName
packageName InstalledPackageInfo
ipkg)
    | Bool
otherwise           = forall a. Pretty a => a -> FilePath
prettyShow (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

--TODO: [code cleanup] decide if we really need this, there's not much in it, and in principle
--      even platform and compiler could be different if we're building things
--      like a server + client with ghc + ghcjs
data ElaboratedSharedConfig
   = ElaboratedSharedConfig {

       ElaboratedSharedConfig -> Platform
pkgConfigPlatform      :: Platform,
       ElaboratedSharedConfig -> Compiler
pkgConfigCompiler      :: Compiler, --TODO: [code cleanup] replace with CompilerInfo
       -- | The programs that the compiler configured (e.g. for GHC, the progs
       -- ghc & ghc-pkg). Once constructed, only the 'configuredPrograms' are
       -- used.
       ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs :: ProgramDb,
       ElaboratedSharedConfig -> ReplOptions
pkgConfigReplOptions :: ReplOptions
     }
  deriving (Int -> ElaboratedSharedConfig -> ShowS
[ElaboratedSharedConfig] -> ShowS
ElaboratedSharedConfig -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ElaboratedSharedConfig] -> ShowS
$cshowList :: [ElaboratedSharedConfig] -> ShowS
show :: ElaboratedSharedConfig -> FilePath
$cshow :: ElaboratedSharedConfig -> FilePath
showsPrec :: Int -> ElaboratedSharedConfig -> ShowS
$cshowsPrec :: Int -> ElaboratedSharedConfig -> ShowS
Show, 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
$cto :: forall x. Rep ElaboratedSharedConfig x -> ElaboratedSharedConfig
$cfrom :: forall x. ElaboratedSharedConfig -> Rep ElaboratedSharedConfig x
Generic, Typeable)
  --TODO: [code cleanup] no Eq instance

instance Binary ElaboratedSharedConfig
instance Structured ElaboratedSharedConfig

data ElaboratedConfiguredPackage
   = ElaboratedConfiguredPackage {
       -- | The 'UnitId' which uniquely identifies this item in a build plan
       ElaboratedConfiguredPackage -> UnitId
elabUnitId        :: UnitId,

       ElaboratedConfiguredPackage -> ComponentId
elabComponentId :: ComponentId,
       ElaboratedConfiguredPackage -> Map ModuleName Module
elabInstantiatedWith :: Map ModuleName Module,
       ElaboratedConfiguredPackage -> Map ModuleName OpenModule
elabLinkedInstantiatedWith :: Map ModuleName OpenModule,

       -- | This is true if this is an indefinite package, or this is a
       -- package with no signatures.  (Notably, it's not true for instantiated
       -- packages.)  The motivation for this is if you ask to build
       -- @foo-indef@, this probably means that you want to typecheck
       -- it, NOT that you want to rebuild all of the various
       -- instantiations of it.
       ElaboratedConfiguredPackage -> Bool
elabIsCanonical :: Bool,

       -- | The 'PackageId' of the originating package
       ElaboratedConfiguredPackage -> PackageId
elabPkgSourceId    :: PackageId,

       -- | Shape of the package/component, for Backpack.
       ElaboratedConfiguredPackage -> ModuleShape
elabModuleShape    :: ModuleShape,

       -- | A total flag assignment for the package.
       -- TODO: Actually this can be per-component if we drop
       -- all flags that don't affect a component.
       ElaboratedConfiguredPackage -> FlagAssignment
elabFlagAssignment   :: Cabal.FlagAssignment,

       -- | The original default flag assignment, used only for reporting.
       ElaboratedConfiguredPackage -> FlagAssignment
elabFlagDefaults     :: Cabal.FlagAssignment,

       ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription :: Cabal.PackageDescription,

       -- | Where the package comes from, e.g. tarball, local dir etc. This
       --   is not the same as where it may be unpacked to for the build.
       ElaboratedConfiguredPackage -> PackageLocation (Maybe FilePath)
elabPkgSourceLocation :: PackageLocation (Maybe FilePath),

       -- | The hash of the source, e.g. the tarball. We don't have this for
       -- local source dir packages.
       ElaboratedConfiguredPackage -> Maybe PackageSourceHash
elabPkgSourceHash     :: Maybe PackageSourceHash,

       -- | Is this package one of the ones specified by location in the
       -- project file? (As opposed to a dependency, or a named package pulled
       -- in)
       ElaboratedConfiguredPackage -> Bool
elabLocalToProject         :: Bool,

       -- | Are we going to build and install this package to the store, or are
       -- we going to build it and register it locally.
       ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle             :: BuildStyle,

       -- | Another way of phrasing 'pkgStanzasAvailable'.
       ElaboratedConfiguredPackage -> ComponentRequestedSpec
elabEnabledSpec      :: ComponentRequestedSpec,

       -- | Which optional stanzas (ie testsuites, benchmarks) can be built.
       -- This means the solver produced a plan that has them available.
       -- This doesn't necessary mean we build them by default.
       ElaboratedConfiguredPackage -> OptionalStanzaSet
elabStanzasAvailable :: OptionalStanzaSet,

       -- | Which optional stanzas the user explicitly asked to enable or
       -- to disable. This tells us which ones we build by default, and
       -- helps with error messages when the user asks to build something
       -- they explicitly disabled.
       --
       -- TODO: The 'Bool' here should be refined into an ADT with three
       -- cases: NotRequested, ExplicitlyRequested and
       -- ImplicitlyRequested.  A stanza is explicitly requested if
       -- the user asked, for this *specific* package, that the stanza
       -- be enabled; it's implicitly requested if the user asked for
       -- all global packages to have this stanza enabled.  The
       -- difference between an explicit and implicit request is
       -- error reporting behavior: if a user asks for tests to be
       -- enabled for a specific package that doesn't have any tests,
       -- we should warn them about it, but we shouldn't complain
       -- that a user enabled tests globally, and some local packages
       -- just happen not to have any tests.  (But perhaps we should
       -- warn if ALL local packages don't have any tests.)
       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,

       -- TODO: make per-component variants of these flags
       ElaboratedConfiguredPackage -> Bool
elabVanillaLib           :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabSharedLib            :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabStaticLib            :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabDynExe               :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabFullyStaticExe       :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabGHCiLib              :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabProfLib              :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabProfExe              :: Bool,
       ElaboratedConfiguredPackage -> ProfDetailLevel
elabProfLibDetail        :: ProfDetailLevel,
       ElaboratedConfiguredPackage -> ProfDetailLevel
elabProfExeDetail        :: ProfDetailLevel,
       ElaboratedConfiguredPackage -> Bool
elabCoverage             :: Bool,
       ElaboratedConfiguredPackage -> OptimisationLevel
elabOptimization         :: OptimisationLevel,
       ElaboratedConfiguredPackage -> Bool
elabSplitObjs            :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabSplitSections        :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabStripLibs            :: Bool,
       ElaboratedConfiguredPackage -> Bool
elabStripExes            :: Bool,
       ElaboratedConfiguredPackage -> DebugInfoLevel
elabDebugInfo            :: DebugInfoLevel,
       ElaboratedConfiguredPackage -> DumpBuildInfo
elabDumpBuildInfo        :: DumpBuildInfo,

       ElaboratedConfiguredPackage -> Map FilePath FilePath
elabProgramPaths          :: Map String FilePath,
       ElaboratedConfiguredPackage -> Map FilePath [FilePath]
elabProgramArgs           :: Map String [String],
       ElaboratedConfiguredPackage -> [FilePath]
elabProgramPathExtra      :: [FilePath],
       ElaboratedConfiguredPackage -> [FilePath]
elabConfigureScriptArgs   :: [String],
       ElaboratedConfiguredPackage -> [FilePath]
elabExtraLibDirs          :: [FilePath],
       ElaboratedConfiguredPackage -> [FilePath]
elabExtraLibDirsStatic    :: [FilePath],
       ElaboratedConfiguredPackage -> [FilePath]
elabExtraFrameworkDirs    :: [FilePath],
       ElaboratedConfiguredPackage -> [FilePath]
elabExtraIncludeDirs      :: [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 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],

       -- Setup.hs related things:

       -- | One of four modes for how we build and interact with the Setup.hs
       -- script, based on whether it's a build-type Custom, with or without
       -- explicit deps and the cabal spec version the .cabal file needs.
       ElaboratedConfiguredPackage -> SetupScriptStyle
elabSetupScriptStyle      :: SetupScriptStyle,

       -- | The version of the Cabal command line interface that we are using
       -- for this package. This is typically the version of the Cabal lib
       -- that the Setup.hs is built against.
       --
       -- TODO: We might want to turn this into a enum,
       -- yet different enum than 'CabalSpecVersion'.
       ElaboratedConfiguredPackage -> Version
elabSetupScriptCliVersion :: Version,

       -- Build time related:
       ElaboratedConfiguredPackage -> [ComponentTarget]
elabConfigureTargets      :: [ComponentTarget],
       ElaboratedConfiguredPackage -> [ComponentTarget]
elabBuildTargets          :: [ComponentTarget],
       ElaboratedConfiguredPackage -> [ComponentTarget]
elabTestTargets           :: [ComponentTarget],
       ElaboratedConfiguredPackage -> [ComponentTarget]
elabBenchTargets          :: [ComponentTarget],
       ElaboratedConfiguredPackage -> Maybe ComponentTarget
elabReplTarget            :: Maybe ComponentTarget,
       ElaboratedConfiguredPackage -> [ComponentTarget]
elabHaddockTargets        :: [ComponentTarget],

       ElaboratedConfiguredPackage -> Bool
elabBuildHaddocks         :: Bool,

       --pkgSourceDir ? -- currently passed in later because they can use temp locations
       --pkgBuildDir  ? -- but could in principle still have it here, with optional instr to use temp loc

       -- | Component/package specific information
       ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp :: ElaboratedPackageOrComponent
   }
  deriving (ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
$c/= :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
== :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
$c== :: ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage -> Bool
Eq, Int -> ElaboratedConfiguredPackage -> ShowS
[ElaboratedConfiguredPackage] -> ShowS
ElaboratedConfiguredPackage -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ElaboratedConfiguredPackage] -> ShowS
$cshowList :: [ElaboratedConfiguredPackage] -> ShowS
show :: ElaboratedConfiguredPackage -> FilePath
$cshow :: ElaboratedConfiguredPackage -> FilePath
showsPrec :: Int -> ElaboratedConfiguredPackage -> ShowS
$cshowsPrec :: Int -> ElaboratedConfiguredPackage -> ShowS
Show, 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
$cto :: forall x.
Rep ElaboratedConfiguredPackage x -> ElaboratedConfiguredPackage
$cfrom :: forall x.
ElaboratedConfiguredPackage -> Rep ElaboratedConfiguredPackage x
Generic, Typeable)

normaliseConfiguredPackage :: ElaboratedSharedConfig
                           -> ElaboratedConfiguredPackage
                           -> ElaboratedConfiguredPackage
normaliseConfiguredPackage :: ElaboratedSharedConfig
-> ElaboratedConfiguredPackage -> ElaboratedConfiguredPackage
normaliseConfiguredPackage ElaboratedSharedConfig{ProgramDb
pkgConfigCompilerProgs :: ProgramDb
pkgConfigCompilerProgs :: ElaboratedSharedConfig -> ProgramDb
pkgConfigCompilerProgs} ElaboratedConfiguredPackage
pkg =
    ElaboratedConfiguredPackage
pkg { elabProgramArgs :: Map FilePath [FilePath]
elabProgramArgs = forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybeWithKey FilePath -> [FilePath] -> Maybe [FilePath]
lookupFilter (ElaboratedConfiguredPackage -> Map FilePath [FilePath]
elabProgramArgs ElaboratedConfiguredPackage
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 [] = forall a. Maybe a
Nothing
    removeEmpty [FilePath]
xs = 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 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 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ConfiguredProgram -> Maybe Version
programVersion

-- | The package/component contains/is a library and so must be registered
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 ->
            -- Tricky! Not only do we have to test if the user selected
            -- a library as a build target, we also have to test if
            -- the library was TRANSITIVELY depended upon, since we will
            -- also require a register in this case.
            --
            -- NB: It would have been far nicer to just unconditionally
            -- register in all cases, but some Custom Setups will fall
            -- over if you try to do that, ESPECIALLY if there actually is
            -- a library but they hadn't built it.
            --
            -- However, as the case of `cpphs-1.20.8` has shown in
            -- #5379, in cases when a monolithic package gets
            -- installed due to its executable components
            -- (i.e. exe:cpphs) into the store we *have* to register
            -- if there's a buildable public library (i.e. lib:cpphs)
            -- that was built and installed into the same store folder
            -- as otherwise this will cause build failures once a
            -- target actually depends on lib:cpphs.
            Bool
build_target Bool -> Bool -> Bool
|| (ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle ElaboratedConfiguredPackage
elab forall a. Eq a => a -> a -> Bool
== BuildStyle
BuildAndInstall Bool -> Bool -> Bool
&&
                             PackageDescription -> Bool
Cabal.hasPublicLib (ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
elab))
            -- the next sub-condition below is currently redundant
            -- (see discussion in #5604 for more details), but it's
            -- being kept intentionally here as a safeguard because if
            -- internal libraries ever start working with
            -- non-per-component builds this condition won't be
            -- redundant anymore.
                         Bool -> Bool -> 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 (forall (t :: * -> *) a. Foldable t => t a -> Bool
null (forall a. Monoid a => (Component -> Bool) -> ComponentDeps a -> a
CD.select (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 (forall (t :: * -> *) a. Foldable t => t a -> Bool
null (ElaboratedConfiguredPackage -> [ComponentTarget]
elabBuildTargets ElaboratedConfiguredPackage
elab))
            then forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ComponentTarget -> Bool
is_lib_target (ElaboratedConfiguredPackage -> [ComponentTarget]
elabBuildTargets ElaboratedConfiguredPackage
elab)
            -- Empty build targets mean we build /everything/;
            -- that means we have to look more carefully to see
            -- if there is anything to register
            else PackageDescription -> Bool
Cabal.hasLibs (ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
elab)
    -- NB: this means we DO NOT reregister if you just built a
    -- single file
    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

-- | Construct the environment needed for the data files to work.
-- This consists of a separate @*_datadir@ variable for each
-- inplace package in the plan.
dataDirsEnvironmentForPlan :: DistDirLayout
                           -> ElaboratedInstallPlan
                           -> [(String, Maybe FilePath)]
dataDirsEnvironmentForPlan :: DistDirLayout
-> ElaboratedInstallPlan -> [(FilePath, Maybe FilePath)]
dataDirsEnvironmentForPlan DistDirLayout
distDirLayout = forall a. [Maybe a] -> [a]
catMaybes
                           forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall ipkg a srcpkg.
(ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a
InstallPlan.foldPlanPackage
                               (forall a b. a -> b -> a
const forall a. Maybe a
Nothing)
                               (DistDirLayout
-> ElaboratedConfiguredPackage -> Maybe (FilePath, Maybe FilePath)
dataDirEnvVarForPackage DistDirLayout
distDirLayout))
                           forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ipkg srcpkg.
GenericInstallPlan ipkg srcpkg -> [GenericPlanPackage ipkg srcpkg]
InstallPlan.toList

-- | Construct an environment variable that points
-- the package's datadir to its correct location.
-- This might be:
-- * 'Just' the package's source directory plus the data subdirectory
--   for inplace packages.
-- * 'Nothing' for packages installed in the store (the path was
--   already included in the package at install/build time).
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 -> forall a. Maybe a
Nothing
     BuildStyle
BuildInplaceOnly -> forall a. a -> Maybe a
Just
       ( PackageDescription -> ShowS
pkgPathEnvVar (ElaboratedConfiguredPackage -> PackageDescription
elabPkgDescription ElaboratedConfiguredPackage
pkg) FilePath
"datadir"
       , forall a. a -> Maybe a
Just 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 PackageId
_packageId Maybe FilePath
_localTar) = FilePath
unpackedPath
    srcPath (RemoteSourceRepoPackage SourceRepoMaybe
_sourceRepo (Just FilePath
localCheckout)) = FilePath
localCheckout
    -- TODO: see https://github.com/haskell/cabal/wiki/Potential-Refactors#unresolvedpkgloc
    srcPath (RemoteSourceRepoPackage SourceRepoMaybe
_sourceRepo Maybe FilePath
Nothing) = forall a. HasCallStack => FilePath -> a
error
      FilePath
"calling dataDirEnvVarForPackage on a not-downloaded repo is an error"
    unpackedPath :: FilePath
unpackedPath =
      DistDirLayout -> PackageId -> FilePath
distUnpackedSrcDirectory DistDirLayout
distDirLayout forall a b. (a -> b) -> a -> b
$ ElaboratedConfiguredPackage -> PackageId
elabPkgSourceId ElaboratedConfiguredPackage
pkg

instance Package ElaboratedConfiguredPackage where
  packageId :: ElaboratedConfiguredPackage -> PackageId
packageId = ElaboratedConfiguredPackage -> PackageId
elabPkgSourceId

instance HasConfiguredId ElaboratedConfiguredPackage where
  configuredId :: ElaboratedConfiguredPackage -> ConfiguredId
configuredId ElaboratedConfiguredPackage
elab =
    PackageId -> Maybe ComponentName -> ComponentId -> ConfiguredId
ConfiguredId (forall pkg. Package pkg => pkg -> PackageId
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
elabUnitId
    nodeNeighbors :: ElaboratedConfiguredPackage -> [Key ElaboratedConfiguredPackage]
nodeNeighbors = ElaboratedConfiguredPackage -> [UnitId]
elabOrderDependencies

instance Binary ElaboratedConfiguredPackage
instance Structured ElaboratedConfiguredPackage

data ElaboratedPackageOrComponent
    = ElabPackage   ElaboratedPackage
    | ElabComponent ElaboratedComponent
  deriving (ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
$c/= :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
== :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
$c== :: ElaboratedPackageOrComponent
-> ElaboratedPackageOrComponent -> Bool
Eq, Int -> ElaboratedPackageOrComponent -> ShowS
[ElaboratedPackageOrComponent] -> ShowS
ElaboratedPackageOrComponent -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ElaboratedPackageOrComponent] -> ShowS
$cshowList :: [ElaboratedPackageOrComponent] -> ShowS
show :: ElaboratedPackageOrComponent -> FilePath
$cshow :: ElaboratedPackageOrComponent -> FilePath
showsPrec :: Int -> ElaboratedPackageOrComponent -> ShowS
$cshowsPrec :: Int -> ElaboratedPackageOrComponent -> ShowS
Show, 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
$cto :: forall x.
Rep ElaboratedPackageOrComponent x -> ElaboratedPackageOrComponent
$cfrom :: forall x.
ElaboratedPackageOrComponent -> Rep ElaboratedPackageOrComponent x
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
_      -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ LibraryName -> ComponentName
CLibName LibraryName
LMainLibName -- there could be more, but default this
        ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> Maybe ComponentName
compComponentName ElaboratedComponent
comp

-- | A user-friendly descriptor for an 'ElaboratedConfiguredPackage'.
elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> String
elabConfiguredName :: Verbosity -> ElaboratedConfiguredPackage -> FilePath
elabConfiguredName Verbosity
verbosity ElaboratedConfiguredPackage
elab
    | Verbosity
verbosity 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 -> forall a. Pretty a => a -> FilePath
prettyShow ComponentName
cname forall a. [a] -> [a] -> [a]
++ FilePath
" from ")
      forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> FilePath
prettyShow (forall pkg. Package pkg => pkg -> PackageId
packageId ElaboratedConfiguredPackage
elab)
    | Bool
otherwise
    = 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 = forall pkg. HasUnitId pkg => pkg -> UnitId
installedUnitId ElaboratedConfiguredPackage
elab,
        distParamComponentId :: ComponentId
distParamComponentId = ElaboratedConfiguredPackage -> ComponentId
elabComponentId ElaboratedConfiguredPackage
elab,
        distParamPackageId :: PackageId
distParamPackageId = ElaboratedConfiguredPackage -> PackageId
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
_ -> 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 = ElaboratedConfiguredPackage -> OptimisationLevel
elabOptimization ElaboratedConfiguredPackage
elab
    }

-- | The full set of dependencies which dictate what order we
-- need to build things in the install plan: "order dependencies"
-- balls everything together.  This is mostly only useful for
-- ordering; if you are, for example, trying to compute what
-- @--dependency@ flags to pass to a Setup script, you need to
-- use 'elabLibDependencies'.  This method is the same as
-- 'nodeNeighbors'.
--
-- NB: this method DOES include setup deps.
elabOrderDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderDependencies ElaboratedConfiguredPackage
elab =
    case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
        -- Important not to have duplicates: otherwise InstallPlan gets
        -- confused.
        ElabPackage ElaboratedPackage
pkg    -> forall a. Ord a => [a] -> [a]
ordNub (forall a. Monoid a => ComponentDeps a -> a
CD.flatDeps (ElaboratedPackage -> ComponentDeps [UnitId]
pkgOrderDependencies ElaboratedPackage
pkg))
        ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [UnitId]
compOrderDependencies ElaboratedComponent
comp

-- | Like 'elabOrderDependencies', but only returns dependencies on
-- libraries.
elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderLibDependencies ElaboratedConfiguredPackage
elab =
    case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
        ElabPackage ElaboratedPackage
pkg    -> forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId) forall a b. (a -> b) -> a -> b
$
                              forall a. Ord a => [a] -> [a]
ordNub forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => ComponentDeps a -> a
CD.flatDeps (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgLibDependencies ElaboratedPackage
pkg)
        ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [UnitId]
compOrderLibDependencies ElaboratedComponent
comp

-- | The library dependencies (i.e., the libraries we depend on, NOT
-- the dependencies of the library), NOT including setup dependencies.
-- These are passed to the @Setup@ script via @--dependency@.
elabLibDependencies :: ElaboratedConfiguredPackage -> [ConfiguredId]
elabLibDependencies :: ElaboratedConfiguredPackage -> [ConfiguredId]
elabLibDependencies ElaboratedConfiguredPackage
elab =
    case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
        ElabPackage ElaboratedPackage
pkg    -> forall a. Ord a => [a] -> [a]
ordNub (forall a. Monoid a => ComponentDeps a -> a
CD.nonSetupDeps (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgLibDependencies ElaboratedPackage
pkg))
        ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [ConfiguredId]
compLibDependencies ElaboratedComponent
comp

-- | Like 'elabOrderDependencies', but only returns dependencies on
-- executables.  (This coincides with 'elabExeDependencies'.)
elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [UnitId]
elabOrderExeDependencies =
    forall a b. (a -> b) -> [a] -> [b]
map ComponentId -> UnitId
newSimpleUnitId forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedConfiguredPackage -> [ComponentId]
elabExeDependencies

-- | The executable dependencies (i.e., the executables we depend on);
-- these are the executables we must add to the PATH before we invoke
-- the setup script.
elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId]
elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId]
elabExeDependencies ElaboratedConfiguredPackage
elab = forall a b. (a -> b) -> [a] -> [b]
map ConfiguredId -> ComponentId
confInstId forall a b. (a -> b) -> a -> b
$
    case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
        ElabPackage ElaboratedPackage
pkg    -> forall a. Monoid a => ComponentDeps a -> a
CD.nonSetupDeps (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgExeDependencies ElaboratedPackage
pkg)
        ElabComponent ElaboratedComponent
comp -> ElaboratedComponent -> [ConfiguredId]
compExeDependencies ElaboratedComponent
comp

-- | This returns the paths of all the executables we depend on; we
-- must add these paths to PATH before invoking the setup script.
-- (This is usually what you want, not 'elabExeDependencies', if you
-- actually want to build something.)
elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath]
elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath]
elabExeDependencyPaths ElaboratedConfiguredPackage
elab =
    case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
        ElabPackage ElaboratedPackage
pkg    -> forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => ComponentDeps a -> a
CD.nonSetupDeps (ElaboratedPackage -> ComponentDeps [(ConfiguredId, FilePath)]
pkgExeDependencyPaths ElaboratedPackage
pkg)
        ElabComponent ElaboratedComponent
comp -> forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd (ElaboratedComponent -> [(ConfiguredId, FilePath)]
compExeDependencyPaths ElaboratedComponent
comp)

-- | The setup dependencies (the library dependencies of the setup executable;
-- note that it is not legal for setup scripts to have executable
-- dependencies at the moment.)
elabSetupDependencies :: ElaboratedConfiguredPackage -> [ConfiguredId]
elabSetupDependencies :: ElaboratedConfiguredPackage -> [ConfiguredId]
elabSetupDependencies ElaboratedConfiguredPackage
elab =
    case ElaboratedConfiguredPackage -> ElaboratedPackageOrComponent
elabPkgOrComp ElaboratedConfiguredPackage
elab of
        ElabPackage ElaboratedPackage
pkg -> forall a. Monoid a => ComponentDeps a -> a
CD.setupDeps (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgLibDependencies ElaboratedPackage
pkg)
        -- TODO: Custom setups not supported for components yet.  When
        -- they are, need to do this differently
        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

-- | The cache files of all our inplace dependencies which,
-- when updated, require us to rebuild.  See #4202 for
-- more details.  Essentially, this is a list of filepaths
-- that, if our dependencies get rebuilt, will themselves
-- get updated.
--
-- Note: the hash of these cache files gets built into
-- the build cache ourselves, which means that we end
-- up tracking transitive dependencies!
--
-- Note: This tracks the "build" cache file, but not
-- "registration" or "config" cache files.  Why not?
-- Arguably we should...
--
-- Note: This is a bit of a hack, because it is not really
-- the hashes of the SOURCES of our (transitive) dependencies
-- that we should use to decide whether or not to rebuild,
-- but the output BUILD PRODUCTS.  The strategy we use
-- here will never work if we want to implement unchanging
-- rebuilds.
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 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall ipkg srcpkg.
GenericInstallPlan ipkg srcpkg
-> UnitId -> [GenericPlanPackage ipkg srcpkg]
InstallPlan.directDeps ElaboratedInstallPlan
plan (forall a. IsNode a => a -> Key a
nodeKey ElaboratedConfiguredPackage
root_elab)
  where
    go :: ElaboratedPlanPackage -> [FilePath]
go = forall ipkg a srcpkg.
(ipkg -> a) -> (srcpkg -> a) -> GenericPlanPackage ipkg srcpkg -> a
InstallPlan.foldPlanPackage (forall a b. a -> b -> a
const []) forall a b. (a -> b) -> a -> b
$ \ElaboratedConfiguredPackage
elab -> do
            forall (f :: * -> *). Alternative f => Bool -> f ()
guard (ElaboratedConfiguredPackage -> BuildStyle
elabBuildStyle ElaboratedConfiguredPackage
elab forall a. Eq a => a -> a -> Bool
== BuildStyle
BuildInplaceOnly)
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ DistDirLayout -> DistDirParams -> ShowS
distPackageCacheFile DistDirLayout
layout (ElaboratedSharedConfig
-> ElaboratedConfiguredPackage -> DistDirParams
elabDistDirParams ElaboratedSharedConfig
sconf ElaboratedConfiguredPackage
elab) FilePath
"build"

-- | Some extra metadata associated with an
-- 'ElaboratedConfiguredPackage' which indicates that the "package"
-- in question is actually a single component to be built.  Arguably
-- it would be clearer if there were an ADT which branched into
-- package work items and component work items, but I've structured
-- it this way to minimize change to the existing code (which I
-- don't feel qualified to rewrite.)
data ElaboratedComponent
   = ElaboratedComponent {
    -- | The name of the component to be built according to the solver
    ElaboratedComponent -> Component
compSolverName :: CD.Component,
    -- | The name of the component to be built.  Nothing if
    -- it's a setup dep.
    ElaboratedComponent -> Maybe ComponentName
compComponentName :: Maybe ComponentName,
    -- | The *external* library dependencies of this component.  We
    -- pass this to the configure script.
    ElaboratedComponent -> [ConfiguredId]
compLibDependencies :: [ConfiguredId],
    -- | In a component prior to instantiation, this list specifies
    -- the 'OpenUnitId's which, after instantiation, are the
    -- actual dependencies of this package.  Note that this does
    -- NOT include signature packages, which do not turn into real
    -- ordering dependencies when we instantiate.  This is intended to be
    -- a purely temporary field, to carry some information to the
    -- instantiation phase. It's more precise than
    -- 'compLibDependencies', and also stores information about internal
    -- dependencies.
    ElaboratedComponent -> [OpenUnitId]
compLinkedLibDependencies :: [OpenUnitId],
    -- | The executable dependencies of this component (including
    -- internal executables).
    ElaboratedComponent -> [ConfiguredId]
compExeDependencies :: [ConfiguredId],
    -- | The @pkg-config@ dependencies of the component
    ElaboratedComponent -> [(PkgconfigName, Maybe PkgconfigVersion)]
compPkgConfigDependencies :: [(PkgconfigName, Maybe PkgconfigVersion)],
    -- | The paths all our executable dependencies will be installed
    -- to once they are installed.
    ElaboratedComponent -> [(ConfiguredId, FilePath)]
compExeDependencyPaths :: [(ConfiguredId, FilePath)],
    -- | The UnitIds of the libraries (identifying elaborated packages/
    -- components) that must be built before this project.  This
    -- is used purely for ordering purposes.  It can contain both
    -- references to definite and indefinite packages; an indefinite
    -- UnitId indicates that we must typecheck that indefinite package
    -- before we can build this one.
    ElaboratedComponent -> [UnitId]
compOrderLibDependencies :: [UnitId]
   }
  deriving (ElaboratedComponent -> ElaboratedComponent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElaboratedComponent -> ElaboratedComponent -> Bool
$c/= :: ElaboratedComponent -> ElaboratedComponent -> Bool
== :: ElaboratedComponent -> ElaboratedComponent -> Bool
$c== :: ElaboratedComponent -> ElaboratedComponent -> Bool
Eq, Int -> ElaboratedComponent -> ShowS
[ElaboratedComponent] -> ShowS
ElaboratedComponent -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ElaboratedComponent] -> ShowS
$cshowList :: [ElaboratedComponent] -> ShowS
show :: ElaboratedComponent -> FilePath
$cshow :: ElaboratedComponent -> FilePath
showsPrec :: Int -> ElaboratedComponent -> ShowS
$cshowsPrec :: Int -> ElaboratedComponent -> ShowS
Show, 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
$cto :: forall x. Rep ElaboratedComponent x -> ElaboratedComponent
$cfrom :: forall x. ElaboratedComponent -> Rep ElaboratedComponent x
Generic)

instance Binary ElaboratedComponent
instance Structured ElaboratedComponent

-- | See 'elabOrderDependencies'.
compOrderDependencies :: ElaboratedComponent -> [UnitId]
compOrderDependencies :: ElaboratedComponent -> [UnitId]
compOrderDependencies ElaboratedComponent
comp =
    ElaboratedComponent -> [UnitId]
compOrderLibDependencies ElaboratedComponent
comp
 forall a. [a] -> [a] -> [a]
++ ElaboratedComponent -> [UnitId]
compOrderExeDependencies ElaboratedComponent
comp

-- | See 'elabOrderExeDependencies'.
compOrderExeDependencies :: ElaboratedComponent -> [UnitId]
compOrderExeDependencies :: ElaboratedComponent -> [UnitId]
compOrderExeDependencies = forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ElaboratedComponent -> [ConfiguredId]
compExeDependencies

data ElaboratedPackage
   = ElaboratedPackage {
       ElaboratedPackage -> ComponentId
pkgInstalledId :: InstalledPackageId,

       -- | The exact dependencies (on other plan packages)
       --
       ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgLibDependencies :: ComponentDeps [ConfiguredId],

       -- | Components which depend (transitively) on an internally
       -- defined library.  These are used by 'elabRequiresRegistration',
       -- to determine if a user-requested build is going to need
       -- a library registration
       --
       ElaboratedPackage -> ComponentDeps [()]
pkgDependsOnSelfLib :: ComponentDeps [()],

       -- | Dependencies on executable packages.
       --
       ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgExeDependencies :: ComponentDeps [ConfiguredId],

       -- | Paths where executable dependencies live.
       --
       ElaboratedPackage -> ComponentDeps [(ConfiguredId, FilePath)]
pkgExeDependencyPaths :: ComponentDeps [(ConfiguredId, FilePath)],

       -- | Dependencies on @pkg-config@ packages.
       -- NB: this is NOT per-component (although it could be)
       -- because Cabal library does not track per-component
       -- pkg-config depends; it always does them all at once.
       --
       ElaboratedPackage -> [(PkgconfigName, Maybe PkgconfigVersion)]
pkgPkgConfigDependencies :: [(PkgconfigName, Maybe PkgconfigVersion)],

       -- | Which optional stanzas (ie testsuites, benchmarks) will actually
       -- be enabled during the package configure step.
       ElaboratedPackage -> OptionalStanzaSet
pkgStanzasEnabled :: OptionalStanzaSet
     }
  deriving (ElaboratedPackage -> ElaboratedPackage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElaboratedPackage -> ElaboratedPackage -> Bool
$c/= :: ElaboratedPackage -> ElaboratedPackage -> Bool
== :: ElaboratedPackage -> ElaboratedPackage -> Bool
$c== :: ElaboratedPackage -> ElaboratedPackage -> Bool
Eq, Int -> ElaboratedPackage -> ShowS
[ElaboratedPackage] -> ShowS
ElaboratedPackage -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ElaboratedPackage] -> ShowS
$cshowList :: [ElaboratedPackage] -> ShowS
show :: ElaboratedPackage -> FilePath
$cshow :: ElaboratedPackage -> FilePath
showsPrec :: Int -> ElaboratedPackage -> ShowS
$cshowsPrec :: Int -> ElaboratedPackage -> ShowS
Show, 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
$cto :: forall x. Rep ElaboratedPackage x -> ElaboratedPackage
$cfrom :: forall x. ElaboratedPackage -> Rep ElaboratedPackage x
Generic)

instance Binary ElaboratedPackage
instance Structured ElaboratedPackage

-- | See 'elabOrderDependencies'.  This gives the unflattened version,
-- which can be useful in some circumstances.
pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId]
pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId]
pkgOrderDependencies ElaboratedPackage
pkg =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId)) (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgLibDependencies ElaboratedPackage
pkg) forall a. Monoid a => a -> a -> a
`Mon.mappend`
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. (a -> b) -> [a] -> [b]
map (ComponentId -> UnitId
newSimpleUnitId forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredId -> ComponentId
confInstId)) (ElaboratedPackage -> ComponentDeps [ConfiguredId]
pkgExeDependencies ElaboratedPackage
pkg)

-- | This is used in the install plan to indicate how the package will be
-- built.
--
data BuildStyle =
    -- | The classic approach where the package is built, then the files
    -- installed into some location and the result registered in a package db.
    --
    -- If the package came from a tarball then it's built in a temp dir and
    -- the results discarded.
    BuildAndInstall

    -- | The package is built, but the files are not installed anywhere,
    -- rather the build dir is kept and the package is registered inplace.
    --
    -- Such packages can still subsequently be installed.
    --
    -- Typically 'BuildAndInstall' packages will only depend on other
    -- 'BuildAndInstall' style packages and not on 'BuildInplaceOnly' ones.
    --
  | BuildInplaceOnly
  deriving (BuildStyle -> BuildStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildStyle -> BuildStyle -> Bool
$c/= :: BuildStyle -> BuildStyle -> Bool
== :: BuildStyle -> BuildStyle -> Bool
$c== :: BuildStyle -> BuildStyle -> Bool
Eq, Int -> BuildStyle -> ShowS
[BuildStyle] -> ShowS
BuildStyle -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [BuildStyle] -> ShowS
$cshowList :: [BuildStyle] -> ShowS
show :: BuildStyle -> FilePath
$cshow :: BuildStyle -> FilePath
showsPrec :: Int -> BuildStyle -> ShowS
$cshowsPrec :: Int -> BuildStyle -> ShowS
Show, 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
$cto :: forall x. Rep BuildStyle x -> BuildStyle
$cfrom :: forall x. BuildStyle -> Rep BuildStyle x
Generic)

instance Binary BuildStyle
instance Structured BuildStyle
instance Semigroup BuildStyle where
    BuildStyle
BuildInplaceOnly <> :: BuildStyle -> BuildStyle -> BuildStyle
<> BuildStyle
_ = BuildStyle
BuildInplaceOnly
    BuildStyle
_ <> BuildStyle
BuildInplaceOnly = BuildStyle
BuildInplaceOnly
    BuildStyle
_ <> BuildStyle
_ = BuildStyle
BuildAndInstall
instance Monoid BuildStyle where
    mempty :: BuildStyle
mempty = BuildStyle
BuildAndInstall
    mappend :: BuildStyle -> BuildStyle -> BuildStyle
mappend = forall a. Semigroup a => a -> a -> a
(<>)

type CabalFileText = LBS.ByteString

type ElaboratedReadyPackage = GenericReadyPackage ElaboratedConfiguredPackage


---------------------------
-- Build targets
--

-- | Specific targets within a package or component to act on e.g. to build,
-- haddock or open a repl.
--
data ComponentTarget = ComponentTarget ComponentName SubComponentTarget
  deriving (ComponentTarget -> ComponentTarget -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComponentTarget -> ComponentTarget -> Bool
$c/= :: ComponentTarget -> ComponentTarget -> Bool
== :: ComponentTarget -> ComponentTarget -> Bool
$c== :: ComponentTarget -> ComponentTarget -> Bool
Eq, Eq 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
min :: ComponentTarget -> ComponentTarget -> ComponentTarget
$cmin :: ComponentTarget -> ComponentTarget -> ComponentTarget
max :: ComponentTarget -> ComponentTarget -> ComponentTarget
$cmax :: ComponentTarget -> ComponentTarget -> ComponentTarget
>= :: ComponentTarget -> ComponentTarget -> Bool
$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
compare :: ComponentTarget -> ComponentTarget -> Ordering
$ccompare :: ComponentTarget -> ComponentTarget -> Ordering
Ord, Int -> ComponentTarget -> ShowS
[ComponentTarget] -> ShowS
ComponentTarget -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ComponentTarget] -> ShowS
$cshowList :: [ComponentTarget] -> ShowS
show :: ComponentTarget -> FilePath
$cshow :: ComponentTarget -> FilePath
showsPrec :: Int -> ComponentTarget -> ShowS
$cshowsPrec :: Int -> ComponentTarget -> ShowS
Show, 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
$cto :: forall x. Rep ComponentTarget x -> ComponentTarget
$cfrom :: forall x. ComponentTarget -> Rep ComponentTarget x
Generic)

instance Binary ComponentTarget
instance Structured ComponentTarget

-- | Unambiguously render a 'ComponentTarget', e.g., to pass
-- to a Cabal Setup script.
showComponentTarget :: PackageId -> ComponentTarget -> String
showComponentTarget :: PackageId -> ComponentTarget -> FilePath
showComponentTarget PackageId
pkgid =
    PackageId -> BuildTarget -> FilePath
Cabal.showBuildTarget PackageId
pkgid 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 :: PackageId -> ComponentTarget -> Maybe FilePath
showTestComponentTarget PackageId
_ (ComponentTarget (CTestName UnqualComponentName
n) SubComponentTarget
_) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Pretty a => a -> FilePath
prettyShow UnqualComponentName
n
showTestComponentTarget PackageId
_ ComponentTarget
_ = 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 :: PackageId -> ComponentTarget -> Maybe FilePath
showBenchComponentTarget PackageId
_ (ComponentTarget (CBenchName UnqualComponentName
n) SubComponentTarget
_) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Pretty a => a -> FilePath
prettyShow UnqualComponentName
n
showBenchComponentTarget PackageId
_ ComponentTarget
_ = 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
_)  = forall a. a -> Maybe a
Just OptionalStanza
TestStanzas
componentOptionalStanza (CD.ComponentBench UnqualComponentName
_) = forall a. a -> Maybe a
Just OptionalStanza
BenchStanzas
componentOptionalStanza Component
_                     = forall a. Maybe a
Nothing

---------------------------
-- Setup.hs script policy
--

-- | There are four major cases for Setup.hs handling:
--
--  1. @build-type@ Custom with a @custom-setup@ section
--  2. @build-type@ Custom without a @custom-setup@ section
--  3. @build-type@ not Custom with @cabal-version >  $our-cabal-version@
--  4. @build-type@ not Custom with @cabal-version <= $our-cabal-version@
--
-- It's also worth noting that packages specifying @cabal-version: >= 1.23@
-- or later that have @build-type@ Custom will always have a @custom-setup@
-- section. Therefore in case 2, the specified @cabal-version@ will always be
-- less than 1.23.
--
-- In cases 1 and 2 we obviously have to build an external Setup.hs script,
-- while in case 4 we can use the internal library API. In case 3 we also have
-- to build an external Setup.hs script because the package needs a later
-- Cabal lib version than we can support internally.
--
data SetupScriptStyle = SetupCustomExplicitDeps
                      | SetupCustomImplicitDeps
                      | SetupNonCustomExternalLib
                      | SetupNonCustomInternalLib
  deriving (SetupScriptStyle -> SetupScriptStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupScriptStyle -> SetupScriptStyle -> Bool
$c/= :: SetupScriptStyle -> SetupScriptStyle -> Bool
== :: SetupScriptStyle -> SetupScriptStyle -> Bool
$c== :: SetupScriptStyle -> SetupScriptStyle -> Bool
Eq, Int -> SetupScriptStyle -> ShowS
[SetupScriptStyle] -> ShowS
SetupScriptStyle -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SetupScriptStyle] -> ShowS
$cshowList :: [SetupScriptStyle] -> ShowS
show :: SetupScriptStyle -> FilePath
$cshow :: SetupScriptStyle -> FilePath
showsPrec :: Int -> SetupScriptStyle -> ShowS
$cshowsPrec :: Int -> SetupScriptStyle -> ShowS
Show, 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
$cto :: forall x. Rep SetupScriptStyle x -> SetupScriptStyle
$cfrom :: forall x. SetupScriptStyle -> Rep SetupScriptStyle x
Generic, Typeable)

instance Binary SetupScriptStyle
instance Structured SetupScriptStyle