{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
module Distribution.Types.LocalBuildConfig
(
PackageBuildDescr (..)
, ComponentBuildDescr (..)
, LocalBuildDescr (..)
, LocalBuildConfig (..)
, BuildOptions (..)
, buildOptionsConfigFlags
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Types.ComponentLocalBuildInfo
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.GivenComponent
import Distribution.Types.PackageDescription
import Distribution.Types.UnitId
import Distribution.PackageDescription
import Distribution.Simple.Compiler
import Distribution.Simple.Flag
import Distribution.Simple.InstallDirs hiding
( absoluteInstallDirs
, prefixRelativeInstallDirs
, substPathTemplate
)
import Distribution.Simple.PackageIndex
import Distribution.Simple.Program.Db (ProgramDb)
import Distribution.Simple.Setup.Config
import Distribution.System
import Distribution.Utils.Path
import Distribution.Compat.Graph (Graph)
data PackageBuildDescr = PackageBuildDescr
{ PackageBuildDescr -> ConfigFlags
configFlags :: ConfigFlags
, PackageBuildDescr -> FlagAssignment
flagAssignment :: FlagAssignment
, PackageBuildDescr -> ComponentRequestedSpec
componentEnabledSpec :: ComponentRequestedSpec
, PackageBuildDescr -> Compiler
compiler :: Compiler
, PackageBuildDescr -> Platform
hostPlatform :: Platform
, PackageBuildDescr -> Maybe (SymbolicPath Pkg 'File)
pkgDescrFile :: Maybe (SymbolicPath Pkg File)
, PackageBuildDescr -> PackageDescription
localPkgDescr :: PackageDescription
, PackageBuildDescr -> InstallDirTemplates
installDirTemplates :: InstallDirTemplates
, PackageBuildDescr -> PackageDBStack
withPackageDB :: PackageDBStack
, :: [UnitId]
}
deriving ((forall x. PackageBuildDescr -> Rep PackageBuildDescr x)
-> (forall x. Rep PackageBuildDescr x -> PackageBuildDescr)
-> Generic PackageBuildDescr
forall x. Rep PackageBuildDescr x -> PackageBuildDescr
forall x. PackageBuildDescr -> Rep PackageBuildDescr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PackageBuildDescr -> Rep PackageBuildDescr x
from :: forall x. PackageBuildDescr -> Rep PackageBuildDescr x
$cto :: forall x. Rep PackageBuildDescr x -> PackageBuildDescr
to :: forall x. Rep PackageBuildDescr x -> PackageBuildDescr
Generic, ReadPrec [PackageBuildDescr]
ReadPrec PackageBuildDescr
Int -> ReadS PackageBuildDescr
ReadS [PackageBuildDescr]
(Int -> ReadS PackageBuildDescr)
-> ReadS [PackageBuildDescr]
-> ReadPrec PackageBuildDescr
-> ReadPrec [PackageBuildDescr]
-> Read PackageBuildDescr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PackageBuildDescr
readsPrec :: Int -> ReadS PackageBuildDescr
$creadList :: ReadS [PackageBuildDescr]
readList :: ReadS [PackageBuildDescr]
$creadPrec :: ReadPrec PackageBuildDescr
readPrec :: ReadPrec PackageBuildDescr
$creadListPrec :: ReadPrec [PackageBuildDescr]
readListPrec :: ReadPrec [PackageBuildDescr]
Read, Int -> PackageBuildDescr -> ShowS
[PackageBuildDescr] -> ShowS
PackageBuildDescr -> String
(Int -> PackageBuildDescr -> ShowS)
-> (PackageBuildDescr -> String)
-> ([PackageBuildDescr] -> ShowS)
-> Show PackageBuildDescr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PackageBuildDescr -> ShowS
showsPrec :: Int -> PackageBuildDescr -> ShowS
$cshow :: PackageBuildDescr -> String
show :: PackageBuildDescr -> String
$cshowList :: [PackageBuildDescr] -> ShowS
showList :: [PackageBuildDescr] -> ShowS
Show)
data ComponentBuildDescr = ComponentBuildDescr
{ ComponentBuildDescr -> Graph ComponentLocalBuildInfo
componentGraph :: Graph ComponentLocalBuildInfo
, ComponentBuildDescr -> Map ComponentName [ComponentLocalBuildInfo]
componentNameMap :: Map ComponentName [ComponentLocalBuildInfo]
, ComponentBuildDescr
-> Map (PackageName, ComponentName) PromisedComponent
promisedPkgs :: Map (PackageName, ComponentName) PromisedComponent
, ComponentBuildDescr -> InstalledPackageIndex
installedPkgs :: InstalledPackageIndex
}
deriving ((forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x)
-> (forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr)
-> Generic ComponentBuildDescr
forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr
forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x
from :: forall x. ComponentBuildDescr -> Rep ComponentBuildDescr x
$cto :: forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr
to :: forall x. Rep ComponentBuildDescr x -> ComponentBuildDescr
Generic, ReadPrec [ComponentBuildDescr]
ReadPrec ComponentBuildDescr
Int -> ReadS ComponentBuildDescr
ReadS [ComponentBuildDescr]
(Int -> ReadS ComponentBuildDescr)
-> ReadS [ComponentBuildDescr]
-> ReadPrec ComponentBuildDescr
-> ReadPrec [ComponentBuildDescr]
-> Read ComponentBuildDescr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ComponentBuildDescr
readsPrec :: Int -> ReadS ComponentBuildDescr
$creadList :: ReadS [ComponentBuildDescr]
readList :: ReadS [ComponentBuildDescr]
$creadPrec :: ReadPrec ComponentBuildDescr
readPrec :: ReadPrec ComponentBuildDescr
$creadListPrec :: ReadPrec [ComponentBuildDescr]
readListPrec :: ReadPrec [ComponentBuildDescr]
Read, Int -> ComponentBuildDescr -> ShowS
[ComponentBuildDescr] -> ShowS
ComponentBuildDescr -> String
(Int -> ComponentBuildDescr -> ShowS)
-> (ComponentBuildDescr -> String)
-> ([ComponentBuildDescr] -> ShowS)
-> Show ComponentBuildDescr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentBuildDescr -> ShowS
showsPrec :: Int -> ComponentBuildDescr -> ShowS
$cshow :: ComponentBuildDescr -> String
show :: ComponentBuildDescr -> String
$cshowList :: [ComponentBuildDescr] -> ShowS
showList :: [ComponentBuildDescr] -> ShowS
Show)
data LocalBuildDescr = LocalBuildDescr
{ LocalBuildDescr -> PackageBuildDescr
packageBuildDescr :: PackageBuildDescr
, LocalBuildDescr -> ComponentBuildDescr
componentBuildDescr :: ComponentBuildDescr
}
deriving ((forall x. LocalBuildDescr -> Rep LocalBuildDescr x)
-> (forall x. Rep LocalBuildDescr x -> LocalBuildDescr)
-> Generic LocalBuildDescr
forall x. Rep LocalBuildDescr x -> LocalBuildDescr
forall x. LocalBuildDescr -> Rep LocalBuildDescr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LocalBuildDescr -> Rep LocalBuildDescr x
from :: forall x. LocalBuildDescr -> Rep LocalBuildDescr x
$cto :: forall x. Rep LocalBuildDescr x -> LocalBuildDescr
to :: forall x. Rep LocalBuildDescr x -> LocalBuildDescr
Generic, ReadPrec [LocalBuildDescr]
ReadPrec LocalBuildDescr
Int -> ReadS LocalBuildDescr
ReadS [LocalBuildDescr]
(Int -> ReadS LocalBuildDescr)
-> ReadS [LocalBuildDescr]
-> ReadPrec LocalBuildDescr
-> ReadPrec [LocalBuildDescr]
-> Read LocalBuildDescr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LocalBuildDescr
readsPrec :: Int -> ReadS LocalBuildDescr
$creadList :: ReadS [LocalBuildDescr]
readList :: ReadS [LocalBuildDescr]
$creadPrec :: ReadPrec LocalBuildDescr
readPrec :: ReadPrec LocalBuildDescr
$creadListPrec :: ReadPrec [LocalBuildDescr]
readListPrec :: ReadPrec [LocalBuildDescr]
Read, Int -> LocalBuildDescr -> ShowS
[LocalBuildDescr] -> ShowS
LocalBuildDescr -> String
(Int -> LocalBuildDescr -> ShowS)
-> (LocalBuildDescr -> String)
-> ([LocalBuildDescr] -> ShowS)
-> Show LocalBuildDescr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalBuildDescr -> ShowS
showsPrec :: Int -> LocalBuildDescr -> ShowS
$cshow :: LocalBuildDescr -> String
show :: LocalBuildDescr -> String
$cshowList :: [LocalBuildDescr] -> ShowS
showList :: [LocalBuildDescr] -> ShowS
Show)
data LocalBuildConfig = LocalBuildConfig
{ :: [String]
, LocalBuildConfig -> ProgramDb
withPrograms :: ProgramDb
, LocalBuildConfig -> BuildOptions
withBuildOptions :: BuildOptions
}
deriving ((forall x. LocalBuildConfig -> Rep LocalBuildConfig x)
-> (forall x. Rep LocalBuildConfig x -> LocalBuildConfig)
-> Generic LocalBuildConfig
forall x. Rep LocalBuildConfig x -> LocalBuildConfig
forall x. LocalBuildConfig -> Rep LocalBuildConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LocalBuildConfig -> Rep LocalBuildConfig x
from :: forall x. LocalBuildConfig -> Rep LocalBuildConfig x
$cto :: forall x. Rep LocalBuildConfig x -> LocalBuildConfig
to :: forall x. Rep LocalBuildConfig x -> LocalBuildConfig
Generic, ReadPrec [LocalBuildConfig]
ReadPrec LocalBuildConfig
Int -> ReadS LocalBuildConfig
ReadS [LocalBuildConfig]
(Int -> ReadS LocalBuildConfig)
-> ReadS [LocalBuildConfig]
-> ReadPrec LocalBuildConfig
-> ReadPrec [LocalBuildConfig]
-> Read LocalBuildConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LocalBuildConfig
readsPrec :: Int -> ReadS LocalBuildConfig
$creadList :: ReadS [LocalBuildConfig]
readList :: ReadS [LocalBuildConfig]
$creadPrec :: ReadPrec LocalBuildConfig
readPrec :: ReadPrec LocalBuildConfig
$creadListPrec :: ReadPrec [LocalBuildConfig]
readListPrec :: ReadPrec [LocalBuildConfig]
Read, Int -> LocalBuildConfig -> ShowS
[LocalBuildConfig] -> ShowS
LocalBuildConfig -> String
(Int -> LocalBuildConfig -> ShowS)
-> (LocalBuildConfig -> String)
-> ([LocalBuildConfig] -> ShowS)
-> Show LocalBuildConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LocalBuildConfig -> ShowS
showsPrec :: Int -> LocalBuildConfig -> ShowS
$cshow :: LocalBuildConfig -> String
show :: LocalBuildConfig -> String
$cshowList :: [LocalBuildConfig] -> ShowS
showList :: [LocalBuildConfig] -> ShowS
Show)
data BuildOptions = BuildOptions
{ BuildOptions -> Bool
withVanillaLib :: Bool
, BuildOptions -> Bool
withProfLib :: Bool
, BuildOptions -> Bool
withProfLibShared :: Bool
, BuildOptions -> Bool
withSharedLib :: Bool
, BuildOptions -> Bool
withStaticLib :: Bool
, BuildOptions -> Bool
withDynExe :: Bool
, BuildOptions -> Bool
withFullyStaticExe :: Bool
, BuildOptions -> Bool
withProfExe :: Bool
, BuildOptions -> ProfDetailLevel
withProfLibDetail :: ProfDetailLevel
, BuildOptions -> ProfDetailLevel
withProfExeDetail :: ProfDetailLevel
, BuildOptions -> OptimisationLevel
withOptimization :: OptimisationLevel
, BuildOptions -> DebugInfoLevel
withDebugInfo :: DebugInfoLevel
, BuildOptions -> Bool
withGHCiLib :: Bool
, BuildOptions -> Bool
splitSections :: Bool
, BuildOptions -> Bool
splitObjs :: Bool
, BuildOptions -> Bool
stripExes :: Bool
, BuildOptions -> Bool
stripLibs :: Bool
, BuildOptions -> Bool
exeCoverage :: Bool
, BuildOptions -> Bool
libCoverage :: Bool
, BuildOptions -> Bool
relocatable :: Bool
}
deriving (BuildOptions -> BuildOptions -> Bool
(BuildOptions -> BuildOptions -> Bool)
-> (BuildOptions -> BuildOptions -> Bool) -> Eq BuildOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BuildOptions -> BuildOptions -> Bool
== :: BuildOptions -> BuildOptions -> Bool
$c/= :: BuildOptions -> BuildOptions -> Bool
/= :: BuildOptions -> BuildOptions -> Bool
Eq, (forall x. BuildOptions -> Rep BuildOptions x)
-> (forall x. Rep BuildOptions x -> BuildOptions)
-> Generic BuildOptions
forall x. Rep BuildOptions x -> BuildOptions
forall x. BuildOptions -> Rep BuildOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BuildOptions -> Rep BuildOptions x
from :: forall x. BuildOptions -> Rep BuildOptions x
$cto :: forall x. Rep BuildOptions x -> BuildOptions
to :: forall x. Rep BuildOptions x -> BuildOptions
Generic, ReadPrec [BuildOptions]
ReadPrec BuildOptions
Int -> ReadS BuildOptions
ReadS [BuildOptions]
(Int -> ReadS BuildOptions)
-> ReadS [BuildOptions]
-> ReadPrec BuildOptions
-> ReadPrec [BuildOptions]
-> Read BuildOptions
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BuildOptions
readsPrec :: Int -> ReadS BuildOptions
$creadList :: ReadS [BuildOptions]
readList :: ReadS [BuildOptions]
$creadPrec :: ReadPrec BuildOptions
readPrec :: ReadPrec BuildOptions
$creadListPrec :: ReadPrec [BuildOptions]
readListPrec :: ReadPrec [BuildOptions]
Read, Int -> BuildOptions -> ShowS
[BuildOptions] -> ShowS
BuildOptions -> String
(Int -> BuildOptions -> ShowS)
-> (BuildOptions -> String)
-> ([BuildOptions] -> ShowS)
-> Show BuildOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BuildOptions -> ShowS
showsPrec :: Int -> BuildOptions -> ShowS
$cshow :: BuildOptions -> String
show :: BuildOptions -> String
$cshowList :: [BuildOptions] -> ShowS
showList :: [BuildOptions] -> ShowS
Show)
instance Binary PackageBuildDescr
instance Structured PackageBuildDescr
instance Binary ComponentBuildDescr
instance Structured ComponentBuildDescr
instance Binary LocalBuildDescr
instance Structured LocalBuildDescr
instance Binary LocalBuildConfig
instance Structured LocalBuildConfig
instance Binary BuildOptions
instance Structured BuildOptions
buildOptionsConfigFlags :: BuildOptions -> ConfigFlags
buildOptionsConfigFlags :: BuildOptions -> ConfigFlags
buildOptionsConfigFlags (BuildOptions{Bool
ProfDetailLevel
DebugInfoLevel
OptimisationLevel
withVanillaLib :: BuildOptions -> Bool
withProfLib :: BuildOptions -> Bool
withProfLibShared :: BuildOptions -> Bool
withSharedLib :: BuildOptions -> Bool
withStaticLib :: BuildOptions -> Bool
withDynExe :: BuildOptions -> Bool
withFullyStaticExe :: BuildOptions -> Bool
withProfExe :: BuildOptions -> Bool
withProfLibDetail :: BuildOptions -> ProfDetailLevel
withProfExeDetail :: BuildOptions -> ProfDetailLevel
withOptimization :: BuildOptions -> OptimisationLevel
withDebugInfo :: BuildOptions -> DebugInfoLevel
withGHCiLib :: BuildOptions -> Bool
splitSections :: BuildOptions -> Bool
splitObjs :: BuildOptions -> Bool
stripExes :: BuildOptions -> Bool
stripLibs :: BuildOptions -> Bool
exeCoverage :: BuildOptions -> Bool
libCoverage :: BuildOptions -> Bool
relocatable :: BuildOptions -> Bool
withVanillaLib :: Bool
withProfLib :: Bool
withProfLibShared :: Bool
withSharedLib :: Bool
withStaticLib :: Bool
withDynExe :: Bool
withFullyStaticExe :: Bool
withProfExe :: Bool
withProfLibDetail :: ProfDetailLevel
withProfExeDetail :: ProfDetailLevel
withOptimization :: OptimisationLevel
withDebugInfo :: DebugInfoLevel
withGHCiLib :: Bool
splitSections :: Bool
splitObjs :: Bool
stripExes :: Bool
stripLibs :: Bool
exeCoverage :: Bool
libCoverage :: Bool
relocatable :: Bool
..}) =
ConfigFlags
forall a. Monoid a => a
mempty
{ configVanillaLib = toFlag $ withVanillaLib
, configSharedLib = toFlag $ withSharedLib
, configStaticLib = toFlag $ withStaticLib
, configDynExe = toFlag $ withDynExe
, configFullyStaticExe = toFlag $ withFullyStaticExe
, configGHCiLib = toFlag $ withGHCiLib
, configProfExe = toFlag $ withProfExe
, configProfLib = toFlag $ withProfLib
, configProfShared = toFlag $ withProfLibShared
, configProf = mempty
,
configProfDetail = toFlag $ withProfExeDetail
, configProfLibDetail = toFlag $ withProfLibDetail
, configCoverage = toFlag $ exeCoverage
, configLibCoverage = mempty
, configRelocatable = toFlag $ relocatable
, configOptimization = toFlag $ withOptimization
, configSplitSections = toFlag $ splitSections
, configSplitObjs = toFlag $ splitObjs
, configStripExes = toFlag $ stripExes
, configStripLibs = toFlag $ stripLibs
, configDebugInfo = toFlag $ withDebugInfo
}