Safe Haskell | None |
---|---|
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 -> ProjectParseResult 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
- readSourcePackageCabalFile :: Verbosity -> FilePath -> ByteString -> IO GenericPackageDescription
- readSourcePackageCabalFile' :: (String -> IO ()) -> FilePath -> ByteString -> IO GenericPackageDescription
- data CabalFileParseError = CabalFileParseError FilePath ByteString (NonEmpty PError) (Maybe Version) [PWarning]
- data ProjectPackageLocation
- data BadPackageLocations = BadPackageLocations (Set ProjectConfigProvenance) [BadPackageLocation]
- data BadPackageLocation
- data BadPackageLocationMatch
- findProjectPackages :: DistDirLayout -> ProjectConfig -> Rebuild [ProjectPackageLocation]
- fetchAndReadSourcePackages :: Verbosity -> DistDirLayout -> Maybe Compiler -> 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
- resolveNumJobsSetting :: Flag Bool -> Flag (Maybe Int) -> ParStratX Int
- checkBadPerPackageCompilerPaths :: [ConfiguredProgram] -> Map PackageName PackageConfig -> IO ()
- data BadPerPackageCompilerPaths = BadPerPackageCompilerPaths [(PackageName, String)]
- maxNumFetchJobs :: Int
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
ProjectConfigBuildOnly | |
Fields
|
Instances
Structured ProjectConfigBuildOnly Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods structure :: Proxy ProjectConfigBuildOnly -> Structure # structureHash' :: Tagged ProjectConfigBuildOnly MD5 | |||||
Monoid ProjectConfigBuildOnly Source # | |||||
Semigroup ProjectConfigBuildOnly Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (<>) :: ProjectConfigBuildOnly -> ProjectConfigBuildOnly -> ProjectConfigBuildOnly # sconcat :: NonEmpty ProjectConfigBuildOnly -> ProjectConfigBuildOnly # stimes :: Integral b => b -> ProjectConfigBuildOnly -> ProjectConfigBuildOnly # | |||||
Generic ProjectConfigBuildOnly Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Associated Types
Methods from :: ProjectConfigBuildOnly -> Rep ProjectConfigBuildOnly x # to :: Rep ProjectConfigBuildOnly x -> ProjectConfigBuildOnly # | |||||
Show ProjectConfigBuildOnly Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods showsPrec :: Int -> ProjectConfigBuildOnly -> ShowS # show :: ProjectConfigBuildOnly -> String # showList :: [ProjectConfigBuildOnly] -> ShowS # | |||||
Binary ProjectConfigBuildOnly Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods put :: ProjectConfigBuildOnly -> Put # get :: Get ProjectConfigBuildOnly # putList :: [ProjectConfigBuildOnly] -> Put # | |||||
Eq ProjectConfigBuildOnly Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (==) :: ProjectConfigBuildOnly -> ProjectConfigBuildOnly -> Bool # (/=) :: ProjectConfigBuildOnly -> ProjectConfigBuildOnly -> Bool # | |||||
type Rep ProjectConfigBuildOnly Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types type Rep ProjectConfigBuildOnly = D1 ('MetaData "ProjectConfigBuildOnly" "Distribution.Client.ProjectConfig.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "ProjectConfigBuildOnly" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "projectConfigVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "projectConfigDryRun") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "projectConfigOnlyDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "projectConfigOnlyDownload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "projectConfigSummaryFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NubList PathTemplate)) :*: S1 ('MetaSel ('Just "projectConfigLogFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate))) :*: (S1 ('MetaSel ('Just "projectConfigBuildReports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ReportLevel)) :*: (S1 ('MetaSel ('Just "projectConfigReportPlanningFailure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "projectConfigSymlinkBinDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))))) :*: (((S1 ('MetaSel ('Just "projectConfigNumJobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe Int))) :*: S1 ('MetaSel ('Just "projectConfigUseSemaphore") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "projectConfigKeepGoing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "projectConfigOfflineMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "projectConfigKeepTempFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))) :*: ((S1 ('MetaSel ('Just "projectConfigHttpTransport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "projectConfigIgnoreExpiry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "projectConfigCacheDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 ('MetaSel ('Just "projectConfigLogsDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "projectConfigClientInstallFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClientInstallFlags))))))) |
data ProjectConfigShared Source #
Project configuration that is shared between all packages in the project. In particular this includes configuration that affects the solver.
Constructors
ProjectConfigShared | |
Fields
|
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
Structured ProjectConfigProvenance Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods structure :: Proxy ProjectConfigProvenance -> Structure # structureHash' :: Tagged ProjectConfigProvenance MD5 | |||||
Generic ProjectConfigProvenance Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Associated Types
Methods from :: ProjectConfigProvenance -> Rep ProjectConfigProvenance x # to :: Rep ProjectConfigProvenance x -> ProjectConfigProvenance # | |||||
Show ProjectConfigProvenance Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods showsPrec :: Int -> ProjectConfigProvenance -> ShowS # show :: ProjectConfigProvenance -> String # showList :: [ProjectConfigProvenance] -> ShowS # | |||||
Binary ProjectConfigProvenance Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods put :: ProjectConfigProvenance -> Put # get :: Get ProjectConfigProvenance # putList :: [ProjectConfigProvenance] -> Put # | |||||
Eq ProjectConfigProvenance Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (==) :: ProjectConfigProvenance -> ProjectConfigProvenance -> Bool # (/=) :: ProjectConfigProvenance -> ProjectConfigProvenance -> Bool # | |||||
Ord ProjectConfigProvenance Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods compare :: ProjectConfigProvenance -> ProjectConfigProvenance -> Ordering # (<) :: ProjectConfigProvenance -> ProjectConfigProvenance -> Bool # (<=) :: ProjectConfigProvenance -> ProjectConfigProvenance -> Bool # (>) :: ProjectConfigProvenance -> ProjectConfigProvenance -> Bool # (>=) :: ProjectConfigProvenance -> ProjectConfigProvenance -> Bool # max :: ProjectConfigProvenance -> ProjectConfigProvenance -> ProjectConfigProvenance # min :: ProjectConfigProvenance -> ProjectConfigProvenance -> ProjectConfigProvenance # | |||||
type Rep ProjectConfigProvenance Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types type Rep ProjectConfigProvenance = D1 ('MetaData "ProjectConfigProvenance" "Distribution.Client.ProjectConfig.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "Implicit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Explicit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectConfigPath))) |
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
PackageConfig | |
Fields
|
Instances
Structured PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types | |||||
Monoid PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods mempty :: PackageConfig # mappend :: PackageConfig -> PackageConfig -> PackageConfig # mconcat :: [PackageConfig] -> PackageConfig # | |||||
Semigroup PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (<>) :: PackageConfig -> PackageConfig -> PackageConfig # sconcat :: NonEmpty PackageConfig -> PackageConfig # stimes :: Integral b => b -> PackageConfig -> PackageConfig # | |||||
Generic PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Associated Types
| |||||
Show PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods showsPrec :: Int -> PackageConfig -> ShowS # show :: PackageConfig -> String # showList :: [PackageConfig] -> ShowS # | |||||
Binary PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types | |||||
Eq PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (==) :: PackageConfig -> PackageConfig -> Bool # (/=) :: PackageConfig -> PackageConfig -> Bool # | |||||
type Rep PackageConfig Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types type Rep PackageConfig = D1 ('MetaData "PackageConfig" "Distribution.Client.ProjectConfig.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "PackageConfig" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "packageConfigProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MapLast String FilePath)) :*: (S1 ('MetaSel ('Just "packageConfigProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MapMappend String [String])) :*: S1 ('MetaSel ('Just "packageConfigProgramPathExtra") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NubList FilePath)))) :*: ((S1 ('MetaSel ('Just "packageConfigFlagAssignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment) :*: S1 ('MetaSel ('Just "packageConfigVanillaLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigSharedLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigStaticLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))) :*: (((S1 ('MetaSel ('Just "packageConfigDynExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigFullyStaticExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigProf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigProfLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "packageConfigProfShared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigProfExe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigProfDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ProfDetailLevel)) :*: S1 ('MetaSel ('Just "packageConfigProfLibDetail") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ProfDetailLevel)))))) :*: ((((S1 ('MetaSel ('Just "packageConfigConfigureArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "packageConfigOptimization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag OptimisationLevel))) :*: (S1 ('MetaSel ('Just "packageConfigProgPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 ('MetaSel ('Just "packageConfigProgSuffix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)))) :*: ((S1 ('MetaSel ('Just "packageConfigExtraLibDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "packageConfigExtraLibDirsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])) :*: (S1 ('MetaSel ('Just "packageConfigExtraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "packageConfigExtraIncludeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))) :*: (((S1 ('MetaSel ('Just "packageConfigGHCiLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigSplitSections") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigSplitObjs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigStripExes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "packageConfigStripLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigTests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))))) :*: (((((S1 ('MetaSel ('Just "packageConfigRelocatable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigDebugInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag DebugInfoLevel))) :*: (S1 ('MetaSel ('Just "packageConfigDumpBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag DumpBuildInfo)) :*: S1 ('MetaSel ('Just "packageConfigRunTests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "packageConfigDocumentation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigHaddockHoogle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigHaddockHtml") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigHaddockHtmlLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String))))) :*: (((S1 ('MetaSel ('Just "packageConfigHaddockForeignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigHaddockExecutables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigHaddockTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigHaddockBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "packageConfigHaddockInternal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigHaddockCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 ('MetaSel ('Just "packageConfigHaddockLinkedSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigHaddockQuickJump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))) :*: ((((S1 ('MetaSel ('Just "packageConfigHaddockHscolourCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "packageConfigHaddockContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate))) :*: (S1 ('MetaSel ('Just "packageConfigHaddockIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 ('MetaSel ('Just "packageConfigHaddockBaseUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))) :*: ((S1 ('MetaSel ('Just "packageConfigHaddockResourcesDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "packageConfigHaddockOutputDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 ('MetaSel ('Just "packageConfigHaddockUseUnicode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "packageConfigHaddockForHackage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag HaddockTarget))))) :*: (((S1 ('MetaSel ('Just "packageConfigTestHumanLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 ('MetaSel ('Just "packageConfigTestMachineLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate))) :*: (S1 ('MetaSel ('Just "packageConfigTestShowDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag TestShowDetails)) :*: S1 ('MetaSel ('Just "packageConfigTestKeepTix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "packageConfigTestWrapper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "packageConfigTestFailWhenNoTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageConfigTestTestOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathTemplate]) :*: S1 ('MetaSel ('Just "packageConfigBenchmarkOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathTemplate])))))))) |
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 # | |||||
Defined in Distribution.Client.ProjectConfig.Types Associated Types
| |||||
(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
Functor (MapMappend k) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods fmap :: (a -> b) -> MapMappend k a -> MapMappend k b # (<$) :: a -> MapMappend k b -> MapMappend k a # | |||||
(Structured k, Structured v) => Structured (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods structure :: Proxy (MapMappend k v) -> Structure # structureHash' :: Tagged (MapMappend k v) MD5 | |||||
(Semigroup v, Ord k) => Monoid (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods mempty :: MapMappend k v # mappend :: MapMappend k v -> MapMappend k v -> MapMappend k v # mconcat :: [MapMappend k v] -> MapMappend k v # | |||||
(Semigroup v, Ord k) => Semigroup (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (<>) :: MapMappend k v -> MapMappend k v -> MapMappend k v # sconcat :: NonEmpty (MapMappend k v) -> MapMappend k v # stimes :: Integral b => b -> MapMappend k v -> MapMappend k v # | |||||
Generic (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Associated Types
Methods from :: MapMappend k v -> Rep (MapMappend k v) x # to :: Rep (MapMappend k v) x -> MapMappend k v # | |||||
(Show k, Show v) => Show (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods showsPrec :: Int -> MapMappend k v -> ShowS # show :: MapMappend k v -> String # showList :: [MapMappend k v] -> ShowS # | |||||
(Binary k, Binary v) => Binary (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods put :: MapMappend k v -> Put # get :: Get (MapMappend k v) # putList :: [MapMappend k v] -> Put # | |||||
(Eq k, Eq v) => Eq (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (==) :: MapMappend k v -> MapMappend k v -> Bool # (/=) :: MapMappend k v -> MapMappend k v -> Bool # | |||||
type Rep (MapMappend k v) Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types type Rep (MapMappend k v) = D1 ('MetaData "MapMappend" "Distribution.Client.ProjectConfig.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'True) (C1 ('MetaCons "MapMappend" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMapMappend") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map k v)))) |
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
BadProjectRootExplicitFileNotFound FilePath | |
BadProjectRootDirNotFound FilePath | |
BadProjectRootAbsoluteFileNotFound FilePath | |
BadProjectRootDirFileNotFound FilePath FilePath | |
BadProjectRootFileBroken FilePath |
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 -> ProjectParseResult 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.
readSourcePackageCabalFile :: Verbosity -> FilePath -> ByteString -> IO GenericPackageDescription Source #
Wrapper for the .cabal
file parser. It reports warnings on higher
verbosity levels and throws CabalFileParseError
on failure.
readSourcePackageCabalFile' :: (String -> IO ()) -> FilePath -> ByteString -> IO GenericPackageDescription Source #
Like readSourcePackageCabalFile
, but the warn
function is an argument.
This is used when reading .cabal
files in indexes, where warnings should
generally be ignored.
data CabalFileParseError Source #
Errors reported upon failing to parse a .cabal
file.
Constructors
CabalFileParseError | |
Instances
Exception CabalFileParseError Source # | |
Defined in Distribution.Client.ProjectConfig Methods toException :: CabalFileParseError -> SomeException # fromException :: SomeException -> Maybe CabalFileParseError # | |
Show CabalFileParseError Source # | Manual instance which skips file contents |
Defined in Distribution.Client.ProjectConfig Methods showsPrec :: Int -> CabalFileParseError -> ShowS # show :: CabalFileParseError -> String # showList :: [CabalFileParseError] -> ShowS # |
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
ProjectPackageLocalCabalFile FilePath | |
ProjectPackageLocalDirectory FilePath FilePath | |
ProjectPackageLocalTarball FilePath | |
ProjectPackageRemoteTarball URI | |
ProjectPackageRemoteRepo SourceRepoList | |
ProjectPackageNamed PackageVersionConstraint |
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
BadPackageLocationFile BadPackageLocationMatch | |
BadLocGlobEmptyMatch String | |
BadLocGlobBadMatches String [BadPackageLocationMatch] | |
BadLocUnexpectedUriScheme String | |
BadLocUnrecognisedUri String | |
BadLocUnrecognised String |
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 -> Maybe Compiler -> 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
SolverSettings | |
Fields
|
Instances
Structured SolverSettings Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types | |||||
Generic SolverSettings Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Associated Types
Methods from :: SolverSettings -> Rep SolverSettings x # to :: Rep SolverSettings x -> SolverSettings # | |||||
Show SolverSettings Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods showsPrec :: Int -> SolverSettings -> ShowS # show :: SolverSettings -> String # showList :: [SolverSettings] -> ShowS # | |||||
Binary SolverSettings Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods put :: SolverSettings -> Put # get :: Get SolverSettings # putList :: [SolverSettings] -> Put # | |||||
Eq SolverSettings Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types Methods (==) :: SolverSettings -> SolverSettings -> Bool # (/=) :: SolverSettings -> SolverSettings -> Bool # | |||||
type Rep SolverSettings Source # | |||||
Defined in Distribution.Client.ProjectConfig.Types type Rep SolverSettings = D1 ('MetaData "SolverSettings" "Distribution.Client.ProjectConfig.Types" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "SolverSettings" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "solverSettingRemoteRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RemoteRepo]) :*: S1 ('MetaSel ('Just "solverSettingLocalNoIndexRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LocalRepo])) :*: (S1 ('MetaSel ('Just "solverSettingConstraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UserConstraint, ConstraintSource)]) :*: (S1 ('MetaSel ('Just "solverSettingPreferences") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PackageVersionConstraint]) :*: S1 ('MetaSel ('Just "solverSettingFlagAssignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment)))) :*: ((S1 ('MetaSel ('Just "solverSettingFlagAssignments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PackageName FlagAssignment)) :*: (S1 ('MetaSel ('Just "solverSettingCabalVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version)) :*: S1 ('MetaSel ('Just "solverSettingSolver") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PreSolver))) :*: (S1 ('MetaSel ('Just "solverSettingAllowOlder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AllowOlder) :*: (S1 ('MetaSel ('Just "solverSettingAllowNewer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AllowNewer) :*: S1 ('MetaSel ('Just "solverSettingMaxBackjumps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))) :*: (((S1 ('MetaSel ('Just "solverSettingReorderGoals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReorderGoals) :*: S1 ('MetaSel ('Just "solverSettingCountConflicts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CountConflicts)) :*: (S1 ('MetaSel ('Just "solverSettingFineGrainedConflicts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FineGrainedConflicts) :*: (S1 ('MetaSel ('Just "solverSettingMinimizeConflictSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MinimizeConflictSet) :*: S1 ('MetaSel ('Just "solverSettingStrongFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StrongFlags)))) :*: ((S1 ('MetaSel ('Just "solverSettingAllowBootLibInstalls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AllowBootLibInstalls) :*: (S1 ('MetaSel ('Just "solverSettingOnlyConstrained") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OnlyConstrained) :*: S1 ('MetaSel ('Just "solverSettingIndexState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TotalIndexState)))) :*: (S1 ('MetaSel ('Just "solverSettingActiveRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ActiveRepos)) :*: (S1 ('MetaSel ('Just "solverSettingIndependentGoals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndependentGoals) :*: S1 ('MetaSel ('Just "solverSettingPreferOldest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PreferOldest))))))) |
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
BuildTimeSettings | |
Fields
|
resolveBuildTimeSettings :: Verbosity -> CabalDirLayout -> ProjectConfig -> BuildTimeSettings Source #
Resolve the project configuration, with all its optional fields, into
BuildTimeSettings
with no optional fields (by applying defaults).
resolveNumJobsSetting Source #
Arguments
:: Flag Bool | Whether to use a semaphore (-jsem) |
-> Flag (Maybe Int) | The number of jobs to run concurrently |
-> ParStratX Int |
Determine the number of jobs (ParStrat) from the project config
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 # |
Globals
maxNumFetchJobs :: Int Source #
The maximum amount of fetch jobs that can run concurrently. For instance, this is used to limit the amount of concurrent downloads from hackage, or the amount of concurrent git clones for source-repository-package stanzas.