Safe Haskell | None |
---|---|
Language | Haskell2010 |
Stack.Types.Config
Description
The Config type.
- data Config = Config {
- configStackRoot :: !(Path Abs Dir)
- configDocker :: !DockerOpts
- configEnvOverride :: !(EnvSettings -> IO EnvOverride)
- configLocalPrograms :: !(Path Abs Dir)
- configConnectionCount :: !Int
- configHideTHLoading :: !Bool
- configPlatform :: !Platform
- configGHCVariant0 :: !(Maybe GHCVariant)
- configLatestSnapshotUrl :: !Text
- configPackageIndices :: ![PackageIndex]
- configSystemGHC :: !Bool
- configInstallGHC :: !Bool
- configSkipGHCCheck :: !Bool
- configSkipMsys :: !Bool
- configCompilerCheck :: !VersionCheck
- configLocalBin :: !(Path Abs Dir)
- configRequireStackVersion :: !VersionRange
- configJobs :: !Int
- configExtraIncludeDirs :: !(Set Text)
- configExtraLibDirs :: !(Set Text)
- configConfigMonoid :: !ConfigMonoid
- configConcurrentTests :: !Bool
- configImage :: !ImageOpts
- configTemplateParams :: !(Map Text Text)
- configScmInit :: !(Maybe SCM)
- configGhcOptions :: !(Map (Maybe PackageName) [Text])
- configSetupInfoLocations :: ![SetupInfoLocation]
- configPvpBounds :: !PvpBounds
- data PackageIndex = PackageIndex {}
- newtype IndexName = IndexName {}
- indexNameText :: IndexName -> Text
- data IndexLocation
- data EnvSettings = EnvSettings {
- esIncludeLocals :: !Bool
- esIncludeGhcPackagePath :: !Bool
- esStackExe :: !Bool
- esLocaleUtf8 :: !Bool
- data ExecOpts = ExecOpts {}
- data ExecOptsExtra
- = ExecOptsPlain
- | ExecOptsEmbellished {
- eoEnvSettings :: !EnvSettings
- eoPackages :: ![String]
- data GlobalOpts = GlobalOpts {}
- data AbstractResolver
- defaultLogLevel :: LogLevel
- data BuildConfig = BuildConfig {
- bcConfig :: !Config
- bcResolver :: !Resolver
- bcWantedCompiler :: !CompilerVersion
- bcPackageEntries :: ![PackageEntry]
- bcExtraDeps :: !(Map PackageName Version)
- bcStackYaml :: !(Path Abs File)
- bcFlags :: !(Map PackageName (Map FlagName Bool))
- bcImplicitGlobal :: !Bool
- bcGHCVariant :: !GHCVariant
- bcRoot :: BuildConfig -> Path Abs Dir
- bcWorkDir :: BuildConfig -> Path Abs Dir
- data EnvConfig = EnvConfig {}
- class (HasBuildConfig r, HasGHCVariant r) => HasEnvConfig r where
- getEnvConfig :: r -> EnvConfig
- data LoadConfig m = LoadConfig {
- lcConfig :: !Config
- lcLoadBuildConfig :: !(Maybe AbstractResolver -> m BuildConfig)
- lcProjectRoot :: !(Maybe (Path Abs Dir))
- data PackageEntry = PackageEntry {
- peExtraDepMaybe :: !(Maybe Bool)
- peValidWanted :: !(Maybe Bool)
- peLocation :: !PackageLocation
- peSubdirs :: ![FilePath]
- peExtraDep :: PackageEntry -> Bool
- data PackageLocation
- data Project = Project {
- projectPackages :: ![PackageEntry]
- projectExtraDeps :: !(Map PackageName Version)
- projectFlags :: !(Map PackageName (Map FlagName Bool))
- projectResolver :: !Resolver
- data Resolver
- resolverName :: Resolver -> Text
- parseResolverText :: MonadThrow m => Text -> m Resolver
- class HasStackRoot env where
- getStackRoot :: env -> Path Abs Dir
- class HasPlatform env where
- getPlatform :: env -> Platform
- class HasGHCVariant env where
- getGHCVariant :: env -> GHCVariant
- class (HasStackRoot env, HasPlatform env) => HasConfig env where
- class HasConfig env => HasBuildConfig env where
- getBuildConfig :: env -> BuildConfig
- data ConfigMonoid = ConfigMonoid {
- configMonoidDockerOpts :: !DockerOptsMonoid
- configMonoidConnectionCount :: !(Maybe Int)
- configMonoidHideTHLoading :: !(Maybe Bool)
- configMonoidLatestSnapshotUrl :: !(Maybe Text)
- configMonoidPackageIndices :: !(Maybe [PackageIndex])
- configMonoidSystemGHC :: !(Maybe Bool)
- configMonoidInstallGHC :: !(Maybe Bool)
- configMonoidSkipGHCCheck :: !(Maybe Bool)
- configMonoidSkipMsys :: !(Maybe Bool)
- configMonoidCompilerCheck :: !(Maybe VersionCheck)
- configMonoidRequireStackVersion :: !VersionRange
- configMonoidOS :: !(Maybe String)
- configMonoidArch :: !(Maybe String)
- configMonoidGHCVariant :: !(Maybe GHCVariant)
- configMonoidJobs :: !(Maybe Int)
- configMonoidExtraIncludeDirs :: !(Set Text)
- configMonoidExtraLibDirs :: !(Set Text)
- configMonoidConcurrentTests :: !(Maybe Bool)
- configMonoidLocalBinPath :: !(Maybe FilePath)
- configMonoidImageOpts :: !ImageOptsMonoid
- configMonoidTemplateParameters :: !(Map Text Text)
- configMonoidScmInit :: !(Maybe SCM)
- configMonoidGhcOptions :: !(Map (Maybe PackageName) [Text])
- configMonoidExtraPath :: ![Path Abs Dir]
- configMonoidSetupInfoLocations :: ![SetupInfoLocation]
- configMonoidPvpBounds :: !(Maybe PvpBounds)
- parseConfigMonoidJSON :: Object -> WarningParser ConfigMonoid
- newtype VersionRangeJSON = VersionRangeJSON {}
- data ConfigException
- = ParseConfigFileException (Path Abs File) ParseException
- | ParseResolverException Text
- | NoProjectConfigFound (Path Abs Dir) (Maybe Text)
- | UnexpectedTarballContents [Path Abs Dir] [Path Abs File]
- | BadStackVersionException VersionRange
- | NoMatchingSnapshot [SnapName]
- | NoSuchDirectory FilePath
- | ParseGHCVariantException String
- askConfig :: (MonadReader env m, HasConfig env) => m Config
- askLatestSnapshotUrl :: (MonadReader env m, HasConfig env) => m Text
- configPackageIndexRoot :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs Dir)
- configPackageIndexCache :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File)
- configPackageIndex :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File)
- configPackageIndexGz :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File)
- configPackageTarball :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> PackageIdentifier -> m (Path Abs File)
- workDirRel :: Path Rel Dir
- configProjectWorkDir :: (HasBuildConfig env, MonadReader env m) => m (Path Abs Dir)
- configInstalledCache :: (HasBuildConfig env, MonadReader env m) => m (Path Abs File)
- platformOnlyRelDir :: (MonadReader env m, HasPlatform env, MonadThrow m) => m (Path Rel Dir)
- platformVariantRelDir :: (MonadReader env m, HasPlatform env, HasGHCVariant env, MonadThrow m) => m (Path Rel Dir)
- configShakeFilesDir :: (MonadReader env m, HasBuildConfig env) => m (Path Abs Dir)
- configLocalUnpackDir :: (MonadReader env m, HasBuildConfig env) => m (Path Abs Dir)
- snapshotsDir :: (MonadReader env m, HasConfig env, HasGHCVariant env, MonadThrow m) => m (Path Abs Dir)
- installationRootDeps :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
- installationRootLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
- compilerVersionDir :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Rel Dir)
- packageDatabaseDeps :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
- packageDatabaseLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
- flagCacheLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir)
- configMiniBuildPlanCache :: (MonadThrow m, MonadReader env m, HasConfig env, HasGHCVariant env) => SnapName -> m (Path Abs File)
- bindirSuffix :: Path Rel Dir
- docDirSuffix :: Path Rel Dir
- hpcDirSuffix :: Path Rel Dir
- extraBinDirs :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Bool -> [Path Abs Dir])
- getMinimalEnvOverride :: (MonadReader env m, HasConfig env, MonadIO m) => m EnvOverride
- minimalEnvSettings :: EnvSettings
- getWhichCompiler :: (MonadReader env m, HasEnvConfig env) => m WhichCompiler
- data ProjectAndConfigMonoid = ProjectAndConfigMonoid !Project !ConfigMonoid
- packageEntryCurrDir :: PackageEntry
- data SCM = Git
- data GHCVariant
- ghcVariantName :: GHCVariant -> String
- ghcVariantSuffix :: GHCVariant -> String
- parseGHCVariant :: MonadThrow m => String -> m GHCVariant
- data DownloadInfo = DownloadInfo {}
- parseDownloadInfoFromObject :: Object -> WarningParser DownloadInfo
- data VersionedDownloadInfo = VersionedDownloadInfo {}
- data SetupInfo = SetupInfo {}
- data SetupInfoLocation
- data PvpBounds
- pvpBoundsText :: PvpBounds -> Text
- parsePvpBounds :: Text -> Either String PvpBounds
Documentation
The top-level Stackage configuration.
Constructors
Config | |
Fields
|
Instances
data PackageIndex Source
Information on a single package index
Constructors
PackageIndex | |
Fields
|
Instances
Unique name for a package index
Constructors
IndexName | |
Fields |
indexNameText :: IndexName -> Text Source
data IndexLocation Source
Location of the package index. This ensures that at least one of Git or HTTP is available.
Instances
data EnvSettings Source
Controls which version of the environment is used
Constructors
EnvSettings | |
Fields
|
Instances
Constructors
ExecOpts | |
Fields
|
data ExecOptsExtra Source
Constructors
ExecOptsPlain | |
ExecOptsEmbellished | |
Fields
|
data GlobalOpts Source
Parsed global command-line options.
Constructors
GlobalOpts | |
Fields
|
Instances
data AbstractResolver Source
Either an actual resolver value, or an abstract description of one (e.g., latest nightly).
Constructors
ARLatestNightly | |
ARLatestLTS | |
ARLatestLTSMajor !Int | |
ARResolver !Resolver | |
ARGlobal |
Instances
defaultLogLevel :: LogLevel Source
Default logging level should be something useful but not crazy.
data BuildConfig Source
A superset of Config
adding information on how to build code. The reason
for this breakdown is because we will need some of the information from
Config
in order to determine the values here.
Constructors
BuildConfig | |
Fields
|
Configuration after the environment has been setup.
Constructors
EnvConfig | |
Fields |
class (HasBuildConfig r, HasGHCVariant r) => HasEnvConfig r where Source
Methods
getEnvConfig :: r -> EnvConfig Source
Instances
HasEnvConfig EnvConfig Source | |
HasEnvConfig config => HasEnvConfig (Env config) Source | |
data LoadConfig m Source
Value returned by loadConfig
.
Constructors
LoadConfig | |
Fields
|
data PackageEntry Source
Constructors
PackageEntry | |
Fields
|
Instances
peExtraDep :: PackageEntry -> Bool Source
Once peValidWanted is removed, this should just become the field name in PackageEntry.
data PackageLocation Source
Constructors
PLFilePath FilePath | Note that we use |
PLHttpTarball Text | |
PLGit Text Text | URL and commit |
Instances
A project is a collection of packages. We can have multiple stack.yaml files, but only one of them may contain project information.
Constructors
Project | |
Fields
|
How we resolve which dependencies to install given a set of packages.
Constructors
ResolverSnapshot SnapName | Use an official snapshot from the Stackage project, either an LTS Haskell or Stackage Nightly |
ResolverCompiler !CompilerVersion | Require a specific compiler version, but otherwise provide no build plan. Intended for use cases where end user wishes to specify all upstream dependencies manually, such as using a dependency solver. |
ResolverCustom !Text !Text | A custom resolver based on the given name and URL. This file is assumed to be completely immutable. |
resolverName :: Resolver -> Text Source
Convert a Resolver into its Text
representation, as will be used by
directory names
parseResolverText :: MonadThrow m => Text -> m Resolver Source
Try to parse a Resolver
from a Text
. Won't work for complex resolvers (like custom).
class HasStackRoot env where Source
Class for environment values which have access to the stack root
Minimal complete definition
Nothing
Methods
getStackRoot :: env -> Path Abs Dir Source
Instances
class HasPlatform env where Source
Class for environment values which have a Platform
Minimal complete definition
Nothing
Methods
getPlatform :: env -> Platform Source
Instances
class HasGHCVariant env where Source
Class for environment values which have a GHCVariant
Minimal complete definition
Nothing
Methods
getGHCVariant :: env -> GHCVariant Source
Instances
class (HasStackRoot env, HasPlatform env) => HasConfig env where Source
Class for environment values that can provide a Config
.
Minimal complete definition
Nothing
class HasConfig env => HasBuildConfig env where Source
Class for environment values that can provide a BuildConfig
.
Methods
getBuildConfig :: env -> BuildConfig Source
Instances
HasBuildConfig EnvConfig Source | |
HasBuildConfig BuildConfig Source | |
HasBuildConfig config => HasBuildConfig (Env config) Source | |
data ConfigMonoid Source
Constructors
Instances
parseConfigMonoidJSON :: Object -> WarningParser ConfigMonoid Source
Parse a partial configuration. Used both to parse both a standalone config file and a project file, so that a sub-parser is not required, which would interfere with warnings for missing fields.
newtype VersionRangeJSON Source
Newtype for non-orphan FromJSON instance.
Constructors
VersionRangeJSON | |
Fields |
Instances
FromJSON VersionRangeJSON Source | Parse VersionRange. |
data ConfigException Source
Constructors
Instances
askConfig :: (MonadReader env m, HasConfig env) => m Config Source
Helper function to ask the environment and apply getConfig
askLatestSnapshotUrl :: (MonadReader env m, HasConfig env) => m Text Source
Get the URL to request the information on the latest snapshots
configPackageIndexRoot :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs Dir) Source
Root for a specific package index
configPackageIndexCache :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File) Source
Location of the 00-index.cache file
configPackageIndex :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File) Source
Location of the 00-index.tar file
configPackageIndexGz :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File) Source
Location of the 00-index.tar.gz file
configPackageTarball :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> PackageIdentifier -> m (Path Abs File) Source
Location of a package tarball
workDirRel :: Path Rel Dir Source
configProjectWorkDir :: (HasBuildConfig env, MonadReader env m) => m (Path Abs Dir) Source
Per-project work dir
configInstalledCache :: (HasBuildConfig env, MonadReader env m) => m (Path Abs File) Source
File containing the installed cache, see Stack.PackageDump
platformOnlyRelDir :: (MonadReader env m, HasPlatform env, MonadThrow m) => m (Path Rel Dir) Source
Relative directory for the platform identifier
platformVariantRelDir :: (MonadReader env m, HasPlatform env, HasGHCVariant env, MonadThrow m) => m (Path Rel Dir) Source
Relative directory for the platform identifier
configShakeFilesDir :: (MonadReader env m, HasBuildConfig env) => m (Path Abs Dir) Source
Path to .shake files.
configLocalUnpackDir :: (MonadReader env m, HasBuildConfig env) => m (Path Abs Dir) Source
Where to unpack packages for local build
snapshotsDir :: (MonadReader env m, HasConfig env, HasGHCVariant env, MonadThrow m) => m (Path Abs Dir) Source
Directory containing snapshots
installationRootDeps :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source
Installation root for dependencies
installationRootLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source
Installation root for locals
compilerVersionDir :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Rel Dir) Source
packageDatabaseDeps :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source
Package database for installing dependencies into
packageDatabaseLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source
Package database for installing local packages into
flagCacheLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source
Directory for holding flag cache information
configMiniBuildPlanCache :: (MonadThrow m, MonadReader env m, HasConfig env, HasGHCVariant env) => SnapName -> m (Path Abs File) Source
Where to store mini build plan caches
bindirSuffix :: Path Rel Dir Source
Suffix applied to an installation root to get the bin dir
docDirSuffix :: Path Rel Dir Source
Suffix applied to an installation root to get the doc dir
hpcDirSuffix :: Path Rel Dir Source
Suffix applied to an installation root to get the hpc dir
extraBinDirs :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Bool -> [Path Abs Dir]) Source
Get the extra bin directories (for the PATH). Puts more local first
Bool indicates whether or not to include the locals
getMinimalEnvOverride :: (MonadReader env m, HasConfig env, MonadIO m) => m EnvOverride Source
Get the minimal environment override, useful for just calling external processes like git or ghc
getWhichCompiler :: (MonadReader env m, HasEnvConfig env) => m WhichCompiler Source
data ProjectAndConfigMonoid Source
Constructors
ProjectAndConfigMonoid !Project !ConfigMonoid |
Instances
(~) * warnings [JSONWarning] => FromJSON (ProjectAndConfigMonoid, warnings) Source | |
packageEntryCurrDir :: PackageEntry Source
A PackageEntry for the current directory, used as a default
A software control system.
Constructors
Git |
data GHCVariant Source
Specialized bariant of GHC (e.g. libgmp4 or integer-simple)
Constructors
GHCStandard | Standard bindist |
GHCGMP4 | Bindist that supports libgmp4 (centos66) |
GHCArch | Bindist built on Arch Linux (bleeding-edge) |
GHCIntegerSimple | Bindist that uses integer-simple |
GHCCustom String | Other bindists |
ghcVariantName :: GHCVariant -> String Source
Render a GHC variant to a String.
ghcVariantSuffix :: GHCVariant -> String Source
Render a GHC variant to a String suffix.
parseGHCVariant :: MonadThrow m => String -> m GHCVariant Source
Parse GHC variant from a String.
parseDownloadInfoFromObject :: Object -> WarningParser DownloadInfo Source
Parse JSON in existing object for DownloadInfo
Constructors
SetupInfo | |
Fields |
data SetupInfoLocation Source
Remote or inline SetupInfo
Constructors
SetupInfoFileOrURL String | |
SetupInfoInline SetupInfo |
Instances
How PVP bounds should be added to .cabal files
Constructors
PvpBoundsNone | |
PvpBoundsUpper | |
PvpBoundsLower | |
PvpBoundsBoth |
pvpBoundsText :: PvpBounds -> Text Source