Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Distribution.Client.ProjectConfig
Description
Handling project configuration.
Synopsis
- data ProjectConfig = ProjectConfig {
- projectPackages :: [String]
- projectPackagesOptional :: [String]
- projectPackagesRepo :: [SourceRepoList]
- projectPackagesNamed :: [PackageVersionConstraint]
- projectConfigBuildOnly :: ProjectConfigBuildOnly
- projectConfigShared :: ProjectConfigShared
- projectConfigProvenance :: Set ProjectConfigProvenance
- projectConfigAllPackages :: PackageConfig
- projectConfigLocalPackages :: PackageConfig
- projectConfigSpecificPackage :: MapMappend PackageName PackageConfig
- newtype ProjectConfigToParse = ProjectConfigToParse ByteString
- data ProjectConfigBuildOnly = ProjectConfigBuildOnly {
- projectConfigVerbosity :: Flag Verbosity
- projectConfigDryRun :: Flag Bool
- projectConfigOnlyDeps :: Flag Bool
- projectConfigOnlyDownload :: Flag Bool
- projectConfigSummaryFile :: NubList PathTemplate
- projectConfigLogFile :: Flag PathTemplate
- projectConfigBuildReports :: Flag ReportLevel
- projectConfigReportPlanningFailure :: Flag Bool
- projectConfigSymlinkBinDir :: Flag FilePath
- projectConfigNumJobs :: Flag (Maybe Int)
- projectConfigUseSemaphore :: Flag Bool
- projectConfigKeepGoing :: Flag Bool
- projectConfigOfflineMode :: Flag Bool
- projectConfigKeepTempFiles :: Flag Bool
- projectConfigHttpTransport :: Flag String
- projectConfigIgnoreExpiry :: Flag Bool
- projectConfigCacheDir :: Flag FilePath
- projectConfigLogsDir :: Flag FilePath
- projectConfigClientInstallFlags :: ClientInstallFlags
- data ProjectConfigShared = ProjectConfigShared {
- projectConfigDistDir :: Flag FilePath
- projectConfigConfigFile :: Flag FilePath
- projectConfigProjectDir :: Flag FilePath
- projectConfigProjectFile :: Flag FilePath
- projectConfigIgnoreProject :: Flag Bool
- projectConfigHcFlavor :: Flag CompilerFlavor
- projectConfigHcPath :: Flag FilePath
- projectConfigHcPkg :: Flag FilePath
- projectConfigHaddockIndex :: Flag PathTemplate
- projectConfigInstallDirs :: InstallDirs (Flag PathTemplate)
- projectConfigPackageDBs :: [Maybe PackageDBCWD]
- projectConfigRemoteRepos :: NubList RemoteRepo
- projectConfigLocalNoIndexRepos :: NubList LocalRepo
- projectConfigActiveRepos :: Flag ActiveRepos
- projectConfigIndexState :: Flag TotalIndexState
- projectConfigStoreDir :: Flag FilePath
- projectConfigConstraints :: [(UserConstraint, ConstraintSource)]
- projectConfigPreferences :: [PackageVersionConstraint]
- projectConfigCabalVersion :: Flag Version
- projectConfigSolver :: Flag PreSolver
- projectConfigAllowOlder :: Maybe AllowOlder
- projectConfigAllowNewer :: Maybe AllowNewer
- projectConfigWriteGhcEnvironmentFilesPolicy :: Flag WriteGhcEnvironmentFilesPolicy
- projectConfigMaxBackjumps :: Flag Int
- projectConfigReorderGoals :: Flag ReorderGoals
- projectConfigCountConflicts :: Flag CountConflicts
- projectConfigFineGrainedConflicts :: Flag FineGrainedConflicts
- projectConfigMinimizeConflictSet :: Flag MinimizeConflictSet
- projectConfigStrongFlags :: Flag StrongFlags
- projectConfigAllowBootLibInstalls :: Flag AllowBootLibInstalls
- projectConfigOnlyConstrained :: Flag OnlyConstrained
- projectConfigPerComponent :: Flag Bool
- projectConfigIndependentGoals :: Flag IndependentGoals
- projectConfigPreferOldest :: Flag PreferOldest
- projectConfigProgPathExtra :: NubList FilePath
- projectConfigMultiRepl :: Flag Bool
- data ProjectConfigProvenance
- data PackageConfig = PackageConfig {
- packageConfigProgramPaths :: MapLast String FilePath
- packageConfigProgramArgs :: MapMappend String [String]
- packageConfigProgramPathExtra :: NubList FilePath
- packageConfigFlagAssignment :: FlagAssignment
- packageConfigVanillaLib :: Flag Bool
- packageConfigSharedLib :: Flag Bool
- packageConfigStaticLib :: Flag Bool
- packageConfigDynExe :: Flag Bool
- packageConfigFullyStaticExe :: Flag Bool
- packageConfigProf :: Flag Bool
- packageConfigProfLib :: Flag Bool
- packageConfigProfShared :: Flag Bool
- packageConfigProfExe :: Flag Bool
- packageConfigProfDetail :: Flag ProfDetailLevel
- packageConfigProfLibDetail :: Flag ProfDetailLevel
- packageConfigConfigureArgs :: [String]
- packageConfigOptimization :: Flag OptimisationLevel
- packageConfigProgPrefix :: Flag PathTemplate
- packageConfigProgSuffix :: Flag PathTemplate
- packageConfigExtraLibDirs :: [FilePath]
- packageConfigExtraLibDirsStatic :: [FilePath]
- packageConfigExtraFrameworkDirs :: [FilePath]
- packageConfigExtraIncludeDirs :: [FilePath]
- packageConfigGHCiLib :: Flag Bool
- packageConfigSplitSections :: Flag Bool
- packageConfigSplitObjs :: Flag Bool
- packageConfigStripExes :: Flag Bool
- packageConfigStripLibs :: Flag Bool
- packageConfigTests :: Flag Bool
- packageConfigBenchmarks :: Flag Bool
- packageConfigCoverage :: Flag Bool
- packageConfigRelocatable :: Flag Bool
- packageConfigDebugInfo :: Flag DebugInfoLevel
- packageConfigDumpBuildInfo :: Flag DumpBuildInfo
- packageConfigRunTests :: Flag Bool
- packageConfigDocumentation :: Flag Bool
- packageConfigHaddockHoogle :: Flag Bool
- packageConfigHaddockHtml :: Flag Bool
- packageConfigHaddockHtmlLocation :: Flag String
- packageConfigHaddockForeignLibs :: Flag Bool
- packageConfigHaddockExecutables :: Flag Bool
- packageConfigHaddockTestSuites :: Flag Bool
- packageConfigHaddockBenchmarks :: Flag Bool
- packageConfigHaddockInternal :: Flag Bool
- packageConfigHaddockCss :: Flag FilePath
- packageConfigHaddockLinkedSource :: Flag Bool
- packageConfigHaddockQuickJump :: Flag Bool
- packageConfigHaddockHscolourCss :: Flag FilePath
- packageConfigHaddockContents :: Flag PathTemplate
- packageConfigHaddockIndex :: Flag PathTemplate
- packageConfigHaddockBaseUrl :: Flag String
- packageConfigHaddockResourcesDir :: Flag String
- packageConfigHaddockOutputDir :: Flag FilePath
- packageConfigHaddockUseUnicode :: Flag Bool
- packageConfigHaddockForHackage :: Flag HaddockTarget
- packageConfigTestHumanLog :: Flag PathTemplate
- packageConfigTestMachineLog :: Flag PathTemplate
- packageConfigTestShowDetails :: Flag TestShowDetails
- packageConfigTestKeepTix :: Flag Bool
- packageConfigTestWrapper :: Flag FilePath
- packageConfigTestFailWhenNoTestSuites :: Flag Bool
- packageConfigTestTestOptions :: [PathTemplate]
- packageConfigBenchmarkOptions :: [PathTemplate]
- newtype MapLast k v = MapLast {
- getMapLast :: Map k v
- newtype MapMappend k v = MapMappend {
- getMapMappend :: Map k v
- findProjectRoot :: Verbosity -> Maybe FilePath -> Maybe FilePath -> IO (Either BadProjectRoot ProjectRoot)
- getProjectRootUsability :: FilePath -> IO ProjectRootUsability
- data ProjectRoot
- data BadProjectRoot
- data ProjectRootUsability
- readProjectConfig :: Verbosity -> HttpTransport -> Flag Bool -> Flag FilePath -> DistDirLayout -> Rebuild ProjectConfigSkeleton
- readGlobalConfig :: Verbosity -> Flag FilePath -> Rebuild ProjectConfig
- readProjectLocalExtraConfig :: Verbosity -> HttpTransport -> DistDirLayout -> Rebuild ProjectConfigSkeleton
- readProjectLocalFreezeConfig :: Verbosity -> HttpTransport -> DistDirLayout -> Rebuild ProjectConfigSkeleton
- reportParseResult :: Verbosity -> String -> FilePath -> ParseResult ProjectConfigSkeleton -> IO ProjectConfigSkeleton
- showProjectConfig :: ProjectConfig -> String
- withGlobalConfig :: Verbosity -> Flag FilePath -> (ProjectConfig -> IO a) -> IO a
- withProjectOrGlobalConfig :: Flag Bool -> IO a -> IO a -> IO a
- writeProjectLocalExtraConfig :: DistDirLayout -> ProjectConfig -> IO ()
- writeProjectLocalFreezeConfig :: DistDirLayout -> ProjectConfig -> IO ()
- writeProjectConfigFile :: FilePath -> ProjectConfig -> IO ()
- commandLineFlagsToProjectConfig :: GlobalFlags -> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig
- onlyTopLevelProvenance :: Set ProjectConfigProvenance -> Set ProjectConfigProvenance
- data ProjectPackageLocation
- data BadPackageLocations = BadPackageLocations (Set ProjectConfigProvenance) [BadPackageLocation]
- data BadPackageLocation
- data BadPackageLocationMatch
- findProjectPackages :: DistDirLayout -> ProjectConfig -> Rebuild [ProjectPackageLocation]
- fetchAndReadSourcePackages :: Verbosity -> DistDirLayout -> ProjectConfigShared -> ProjectConfigBuildOnly -> [ProjectPackageLocation] -> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
- lookupLocalPackageConfig :: (Semigroup a, Monoid a) => (PackageConfig -> a) -> ProjectConfig -> PackageName -> a
- projectConfigWithBuilderRepoContext :: Verbosity -> BuildTimeSettings -> (RepoContext -> IO a) -> IO a
- projectConfigWithSolverRepoContext :: Verbosity -> ProjectConfigShared -> ProjectConfigBuildOnly -> (RepoContext -> IO a) -> IO a
- data SolverSettings = SolverSettings {
- solverSettingRemoteRepos :: [RemoteRepo]
- solverSettingLocalNoIndexRepos :: [LocalRepo]
- solverSettingConstraints :: [(UserConstraint, ConstraintSource)]
- solverSettingPreferences :: [PackageVersionConstraint]
- solverSettingFlagAssignment :: FlagAssignment
- solverSettingFlagAssignments :: Map PackageName FlagAssignment
- solverSettingCabalVersion :: Maybe Version
- solverSettingSolver :: PreSolver
- solverSettingAllowOlder :: AllowOlder
- solverSettingAllowNewer :: AllowNewer
- solverSettingMaxBackjumps :: Maybe Int
- solverSettingReorderGoals :: ReorderGoals
- solverSettingCountConflicts :: CountConflicts
- solverSettingFineGrainedConflicts :: FineGrainedConflicts
- solverSettingMinimizeConflictSet :: MinimizeConflictSet
- solverSettingStrongFlags :: StrongFlags
- solverSettingAllowBootLibInstalls :: AllowBootLibInstalls
- solverSettingOnlyConstrained :: OnlyConstrained
- solverSettingIndexState :: Maybe TotalIndexState
- solverSettingActiveRepos :: Maybe ActiveRepos
- solverSettingIndependentGoals :: IndependentGoals
- solverSettingPreferOldest :: PreferOldest
- resolveSolverSettings :: ProjectConfig -> SolverSettings
- data BuildTimeSettings = BuildTimeSettings {
- buildSettingDryRun :: Bool
- buildSettingOnlyDeps :: Bool
- buildSettingOnlyDownload :: Bool
- buildSettingSummaryFile :: [PathTemplate]
- buildSettingLogFile :: Maybe (Compiler -> Platform -> PackageId -> UnitId -> FilePath)
- buildSettingLogVerbosity :: Verbosity
- buildSettingBuildReports :: ReportLevel
- buildSettingReportPlanningFailure :: Bool
- buildSettingSymlinkBinDir :: [FilePath]
- buildSettingNumJobs :: ParStratInstall
- buildSettingKeepGoing :: Bool
- buildSettingOfflineMode :: Bool
- buildSettingKeepTempFiles :: Bool
- buildSettingRemoteRepos :: [RemoteRepo]
- buildSettingLocalNoIndexRepos :: [LocalRepo]
- buildSettingCacheDir :: FilePath
- buildSettingHttpTransport :: Maybe String
- buildSettingIgnoreExpiry :: Bool
- buildSettingProgPathExtra :: [FilePath]
- buildSettingHaddockOpen :: Bool
- resolveBuildTimeSettings :: Verbosity -> CabalDirLayout -> ProjectConfig -> BuildTimeSettings
- checkBadPerPackageCompilerPaths :: [ConfiguredProgram] -> Map PackageName PackageConfig -> IO ()
- data BadPerPackageCompilerPaths = BadPerPackageCompilerPaths [(PackageName, String)]
Types for project config
data ProjectConfig Source #
This type corresponds directly to what can be written in the
cabal.project
file. Other sources of configuration can also be injected
into this type, such as the user-wide config file and the
command line of cabal configure
or cabal build
.
Since it corresponds to the external project file it is an instance of
Monoid
and all the fields can be empty. This also means there has to
be a step where we resolve configuration. At a minimum resolving means
applying defaults but it can also mean merging information from multiple
sources. For example for package-specific configuration the project file
can specify configuration that applies to all local packages, and then
additional configuration for a specific package.
Future directions: multiple profiles, conditionals. If we add these features then the gap between configuration as written in the config file and resolved settings we actually use will become even bigger.
Constructors
ProjectConfig | |
Fields
|
Instances
newtype ProjectConfigToParse Source #
The project configuration is configuration that is parsed but parse configuration may import more configuration. Holds the unparsed contents of an imported file contributing to the project config.
Constructors
ProjectConfigToParse ByteString |
data ProjectConfigBuildOnly Source #
That part of the project configuration that only affects how we build and not the value of the things we build. This means this information does not need to be tracked for changes since it does not affect the outcome.
Constructors
Instances
data ProjectConfigShared Source #
Project configuration that is shared between all packages in the project. In particular this includes configuration that affects the solver.
Constructors
Instances
data ProjectConfigProvenance Source #
Specifies the provenance of project configuration, whether defaults were used or if the configuration was read from an explicit file path.
Constructors
Implicit | The configuration is implicit due to no explicit configuration
being found. See |
Explicit ProjectConfigPath | The path the project configuration was explicitly read from.
| The configuration was explicitly read from the specified |
Instances
data PackageConfig Source #
Project configuration that is specific to each package, that is where we can in principle have different values for different packages in the same project.
Constructors
Instances
Newtype wrapper for Map
that provides a Monoid
instance that takes
the last value rather than the first value for overlapping keys.
Constructors
MapLast | |
Fields
|
Instances
Functor (MapLast k) Source # | |
(Structured k, Structured v) => Structured (MapLast k v) Source # | |
Defined in Distribution.Client.ProjectConfig.Types | |
Ord k => Monoid (MapLast k v) Source # | |
Ord k => Semigroup (MapLast k v) Source # | |
Generic (MapLast k v) Source # | |
(Show k, Show v) => Show (MapLast k v) Source # | |
(Binary k, Binary v) => Binary (MapLast k v) Source # | |
(Eq k, Eq v) => Eq (MapLast k v) Source # | |
type Rep (MapLast k v) Source # | |
Defined in Distribution.Client.ProjectConfig.Types |
newtype MapMappend k v Source #
Newtype wrapper for Map
that provides a Monoid
instance that
mappend
s values of overlapping keys rather than taking the first.
Constructors
MapMappend | |
Fields
|
Instances
Project root
Arguments
:: Verbosity | |
-> Maybe FilePath | Explicit project directory |
-> Maybe FilePath | Explicit project file |
-> IO (Either BadProjectRoot ProjectRoot) |
Find the root of this project.
The project directory will be one of the following:
1. mprojectDir
when present
2. The first directory containing mprojectFile
/cabal.project
, starting from the current directory
and recursively checking parent directories
3. The current directory
getProjectRootUsability :: FilePath -> IO ProjectRootUsability Source #
Get ProjectRootUsability
of a given file
data ProjectRoot Source #
Information about the root directory of the project.
It can either be an implicit project root in the current dir if no
cabal.project
file is found, or an explicit root if either
the file is found or the project root directory was specified.
Constructors
ProjectRootImplicit FilePath | An implicit project root. It contains the absolute project root dir. |
ProjectRootExplicit FilePath FilePath | An explicit project root. It contains the absolute project
root dir and the relative |
ProjectRootExplicitAbsolute FilePath FilePath | An explicit, absolute project root dir and an explicit, absolute
|
Instances
Show ProjectRoot Source # | |
Defined in Distribution.Client.DistDirLayout Methods showsPrec :: Int -> ProjectRoot -> ShowS # show :: ProjectRoot -> String # showList :: [ProjectRoot] -> ShowS # | |
Eq ProjectRoot Source # | |
Defined in Distribution.Client.DistDirLayout |
data BadProjectRoot Source #
Errors returned by findProjectRoot
.
Constructors
Instances
Exception BadProjectRoot Source # | |
Defined in Distribution.Client.ProjectConfig Methods toException :: BadProjectRoot -> SomeException # | |
Show BadProjectRoot Source # | |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> BadProjectRoot -> ShowS # show :: BadProjectRoot -> String # showList :: [BadProjectRoot] -> ShowS # | |
Eq BadProjectRoot Source # | |
Defined in Distribution.Client.ProjectConfig Methods (==) :: BadProjectRoot -> BadProjectRoot -> Bool # (/=) :: BadProjectRoot -> BadProjectRoot -> Bool # |
data ProjectRootUsability Source #
State of the project file, encodes if the file can be used
Constructors
ProjectRootUsabilityPresentAndUsable | The file is present and can be used |
ProjectRootUsabilityPresentAndUnusable | The file is present but can't be used (e.g. broken symlink) |
ProjectRootUsabilityNotPresent | The file is not present |
Instances
Show ProjectRootUsability Source # | |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> ProjectRootUsability -> ShowS # show :: ProjectRootUsability -> String # showList :: [ProjectRootUsability] -> ShowS # | |
Eq ProjectRootUsability Source # | |
Defined in Distribution.Client.ProjectConfig Methods (==) :: ProjectRootUsability -> ProjectRootUsability -> Bool # (/=) :: ProjectRootUsability -> ProjectRootUsability -> Bool # |
Project config files
Arguments
:: Verbosity | |
-> HttpTransport | |
-> Flag Bool | --ignore-project |
-> Flag FilePath | |
-> DistDirLayout | |
-> Rebuild ProjectConfigSkeleton |
Read all the config relevant for a project. This includes the project file if any, plus other global config.
readGlobalConfig :: Verbosity -> Flag FilePath -> Rebuild ProjectConfig Source #
Read the user's cabal-install config file.
readProjectLocalExtraConfig :: Verbosity -> HttpTransport -> DistDirLayout -> Rebuild ProjectConfigSkeleton Source #
Reads a cabal.project.local
file in the given project root dir,
or returns empty. This file gets written by cabal configure
, or in
principle can be edited manually or by other tools.
readProjectLocalFreezeConfig :: Verbosity -> HttpTransport -> DistDirLayout -> Rebuild ProjectConfigSkeleton Source #
Reads a cabal.project.freeze
file in the given project root dir,
or returns empty. This file gets written by cabal freeze
, or in
principle can be edited manually or by other tools.
reportParseResult :: Verbosity -> String -> FilePath -> ParseResult ProjectConfigSkeleton -> IO ProjectConfigSkeleton Source #
showProjectConfig :: ProjectConfig -> String Source #
Render the ProjectConfig
format.
For the moment this is implemented in terms of a pretty printer for the legacy configuration types, plus a conversion.
writeProjectLocalExtraConfig :: DistDirLayout -> ProjectConfig -> IO () Source #
Write a cabal.project.local
file in the given project root dir.
writeProjectLocalFreezeConfig :: DistDirLayout -> ProjectConfig -> IO () Source #
Write a cabal.project.freeze
file in the given project root dir.
writeProjectConfigFile :: FilePath -> ProjectConfig -> IO () Source #
Write in the cabal.project
format to the given file.
commandLineFlagsToProjectConfig :: GlobalFlags -> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig Source #
Convert configuration from the cabal configure
or cabal build
command
line into a ProjectConfig
value that can combined with configuration from
other sources.
At the moment this uses the legacy command line flag types. See
LegacyProjectConfig
for an explanation.
onlyTopLevelProvenance :: Set ProjectConfigProvenance -> Set ProjectConfigProvenance Source #
Filter out non-top-level project configs.
Packages within projects
data ProjectPackageLocation Source #
The location of a package as part of a project. Local file paths are either absolute (if the user specified it as such) or they are relative to the project root.
Constructors
Instances
Show ProjectPackageLocation Source # | |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> ProjectPackageLocation -> ShowS # show :: ProjectPackageLocation -> String # showList :: [ProjectPackageLocation] -> ShowS # |
data BadPackageLocations Source #
Exception thrown by findProjectPackages
.
Constructors
BadPackageLocations (Set ProjectConfigProvenance) [BadPackageLocation] |
Instances
Exception BadPackageLocations Source # | |
Defined in Distribution.Client.ProjectConfig Methods toException :: BadPackageLocations -> SomeException # fromException :: SomeException -> Maybe BadPackageLocations # | |
Show BadPackageLocations Source # | |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> BadPackageLocations -> ShowS # show :: BadPackageLocations -> String # showList :: [BadPackageLocations] -> ShowS # |
data BadPackageLocation Source #
Constructors
Instances
Show BadPackageLocation Source # | |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> BadPackageLocation -> ShowS # show :: BadPackageLocation -> String # showList :: [BadPackageLocation] -> ShowS # |
data BadPackageLocationMatch Source #
Constructors
BadLocUnexpectedFile String | |
BadLocNonexistantFile String | |
BadLocDirNoCabalFile String | |
BadLocDirManyCabalFiles String |
Instances
Show BadPackageLocationMatch Source # | |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> BadPackageLocationMatch -> ShowS # show :: BadPackageLocationMatch -> String # showList :: [BadPackageLocationMatch] -> ShowS # |
findProjectPackages :: DistDirLayout -> ProjectConfig -> Rebuild [ProjectPackageLocation] Source #
Determines the location of all packages mentioned in the project configuration.
Throws BadPackageLocations
.
fetchAndReadSourcePackages :: Verbosity -> DistDirLayout -> ProjectConfigShared -> ProjectConfigBuildOnly -> [ProjectPackageLocation] -> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)] Source #
Read the .cabal
files for a set of packages. For remote tarballs and
VCS source repos this also fetches them if needed.
Note here is where we convert from project-root relative paths to absolute paths.
Resolving configuration
lookupLocalPackageConfig :: (Semigroup a, Monoid a) => (PackageConfig -> a) -> ProjectConfig -> PackageName -> a Source #
Look up a PackageConfig
field in the ProjectConfig
for a specific
PackageName
. This returns the configuration that applies to all local
packages plus any package-specific configuration for this package.
projectConfigWithBuilderRepoContext :: Verbosity -> BuildTimeSettings -> (RepoContext -> IO a) -> IO a Source #
Use a RepoContext
based on the BuildTimeSettings
.
projectConfigWithSolverRepoContext :: Verbosity -> ProjectConfigShared -> ProjectConfigBuildOnly -> (RepoContext -> IO a) -> IO a Source #
Use a RepoContext
, but only for the solver. The solver does not use the
full facilities of the RepoContext
so we can get away with making one
that doesn't have an http transport. And that avoids having to have access
to the BuildTimeSettings
data SolverSettings Source #
Resolved configuration for the solver. The idea is that this is easier to
use than the raw configuration because in the raw configuration everything
is optional (monoidial). In the BuildTimeSettings
every field is filled
in, if only with the defaults.
Use resolveSolverSettings
to make one from the project config (by
applying defaults etc).
Constructors
Instances
resolveSolverSettings :: ProjectConfig -> SolverSettings Source #
Resolve the project configuration, with all its optional fields, into
SolverSettings
with no optional fields (by applying defaults).
data BuildTimeSettings Source #
Resolved configuration for things that affect how we build and not the
value of the things we build. The idea is that this is easier to use than
the raw configuration because in the raw configuration everything is
optional (monoidial). In the BuildTimeSettings
every field is filled in,
if only with the defaults.
Use resolveBuildTimeSettings
to make one from the project config (by
applying defaults etc).
Constructors
resolveBuildTimeSettings :: Verbosity -> CabalDirLayout -> ProjectConfig -> BuildTimeSettings Source #
Resolve the project configuration, with all its optional fields, into
BuildTimeSettings
with no optional fields (by applying defaults).
Checking configuration
checkBadPerPackageCompilerPaths :: [ConfiguredProgram] -> Map PackageName PackageConfig -> IO () Source #
The project configuration is not allowed to specify program locations for programs used by the compiler as these have to be the same for each set of packages.
We cannot check this until we know which programs the compiler uses, which in principle is not until we've configured the compiler.
Throws BadPerPackageCompilerPaths
data BadPerPackageCompilerPaths Source #
Constructors
BadPerPackageCompilerPaths [(PackageName, String)] |
Instances
Exception BadPerPackageCompilerPaths Source # | |
Show BadPerPackageCompilerPaths Source # | |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> BadPerPackageCompilerPaths -> ShowS # show :: BadPerPackageCompilerPaths -> String # showList :: [BadPerPackageCompilerPaths] -> ShowS # |