stack-1.3.0: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.Types.Config

Contents

Description

The Config type.

Synopsis

Main configuration types and classes

HasPlatform & HasStackRoot

class HasPlatform env where Source

Class for environment values which have a Platform

Minimal complete definition

Nothing

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

data PlatformVariant Source

A variant of the platform, used to differentiate Docker builds from host

Config & HasConfig

data Config Source

The top-level Stackage configuration.

Constructors

Config 

Fields

configStackRoot :: !(Path Abs Dir)

~/.stack more often than not

configWorkDir :: !(Path Rel Dir)

this allows to override .stack-work directory

configUserConfigPath :: !(Path Abs File)

Path to user configuration file (usually ~.stackconfig.yaml)

configBuild :: !BuildOpts

Build configuration

configDocker :: !DockerOpts

Docker configuration

configNix :: !NixOpts

Execution environment (e.g nix-shell) configuration

configEnvOverride :: !(EnvSettings -> IO EnvOverride)

Environment variables to be passed to external tools

configLocalProgramsBase :: !(Path Abs Dir)

Non-platform-specific path containing local installations

configLocalPrograms :: !(Path Abs Dir)

Path containing local installations (mainly GHC)

configConnectionCount :: !Int

How many concurrent connections are allowed when downloading

configHideTHLoading :: !Bool

Hide the Template Haskell "Loading package ..." messages from the console

configPlatform :: !Platform

The platform we're building for, used in many directory names

configPlatformVariant :: !PlatformVariant

Variant of the platform, also used in directory names

configGHCVariant0 :: !(Maybe GHCVariant)

The variant of GHC requested by the user. In most cases, use BuildConfig or MiniConfigs version instead, which will have an auto-detected default.

configGHCBuild :: !(Maybe CompilerBuild)

Override build of the compiler distribution (e.g. standard, gmp4, tinfo6)

configUrls :: !Urls

URLs for other files used by stack. TODO: Better document e.g. The latest snapshot file. A build plan name (e.g. lts5.9.yaml) is appended when downloading the build plan actually.

configPackageIndices :: ![PackageIndex]

Information on package indices. This is left biased, meaning that packages in an earlier index will shadow those in a later index.

Warning: if you override packages in an index vs what's available upstream, you may correct your compiled snapshots, as different projects may have different definitions of what pkg-ver means! This feature is primarily intended for adding local packages, not overriding. Overriding is better accomplished by adding to your list of packages.

Note that indices specified in a later config file will override previous indices, not extend them.

Using an assoc list instead of a Map to keep track of priority

configSystemGHC :: !Bool

Should we use the system-installed GHC (on the PATH) if available? Can be overridden by command line options.

configInstallGHC :: !Bool

Should we automatically install GHC if missing or the wrong version is available? Can be overridden by command line options.

configSkipGHCCheck :: !Bool

Don't bother checking the GHC version or architecture.

configSkipMsys :: !Bool

On Windows: don't use a sandboxed MSYS

configCompilerCheck :: !VersionCheck

Specifies which versions of the compiler are acceptable.

configLocalBin :: !(Path Abs Dir)

Directory we should install executables into

configRequireStackVersion :: !VersionRange

Require a version of stack within this range.

configJobs :: !Int

How many concurrent jobs to run, defaults to number of capabilities

configOverrideGccPath :: !(Maybe (Path Abs File))

Optional gcc override path

configExtraIncludeDirs :: !(Set (Path Abs Dir))
  • -extra-include-dirs arguments
configExtraLibDirs :: !(Set (Path Abs Dir))
  • -extra-lib-dirs arguments
configConcurrentTests :: !Bool

Run test suites concurrently

configImage :: !ImageOpts
 
configTemplateParams :: !(Map Text Text)

Parameters for templates.

configScmInit :: !(Maybe SCM)

Initialize SCM (e.g. git) when creating new projects.

configGhcOptions :: !GhcOptions

Additional GHC options to apply to either all packages (Nothing) or a specific package (Just).

configSetupInfoLocations :: ![SetupInfoLocation]

Additional SetupInfo (inline or remote) to use to find tools.

configPvpBounds :: !PvpBounds

How PVP upper bounds should be added to packages

configModifyCodePage :: !Bool

Force the code page to UTF-8 on Windows

configExplicitSetupDeps :: !(Map (Maybe PackageName) Bool)

See explicitSetupDeps. Nothing provides the default value.

configRebuildGhcOptions :: !Bool

Rebuild on GHC options changes

configApplyGhcOptions :: !ApplyGhcOptions

Which packages to ghc-options on the command line apply to?

configAllowNewer :: !Bool

Ignore version ranges in .cabal files. Funny naming chosen to match cabal.

configDefaultTemplate :: !(Maybe TemplateName)

The default template to use when none is specified. (If Nothing, the default default is used.)

configAllowDifferentUser :: !Bool

Allow users other than the stack root owner to use the stack installation.

configPackageCaches :: !(IORef (Maybe (Map PackageIdentifier (PackageIndex, PackageCache))))

In memory cache of hackage index.

configDumpLogs :: !DumpLogs

Dump logs of local non-dependencies when doing a build.

configMaybeProject :: !(Maybe (Project, Path Abs File))

Just when a local project can be found, Nothing when stack must fall back on the implicit global project.

class (HasStackRoot env, HasPlatform env) => HasConfig env where Source

Class for environment values that can provide a Config.

Minimal complete definition

Nothing

Methods

getConfig :: env -> Config Source

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

explicitSetupDeps :: (MonadReader env m, HasConfig env) => PackageName -> m Bool Source

Provide an explicit list of package dependencies when running a custom Setup.hs

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

BuildConfig & HasBuildConfig

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

bcConfig :: !Config
 
bcResolver :: !LoadedResolver

How we resolve which dependencies to install given a set of packages.

bcWantedMiniBuildPlan :: !MiniBuildPlan

Compiler version wanted for this build

bcPackageEntries :: ![PackageEntry]

Local packages

bcExtraDeps :: !(Map PackageName Version)

Extra dependencies specified in configuration.

These dependencies will not be installed to a shared location, and will override packages provided by the resolver.

bcExtraPackageDBs :: ![Path Abs Dir]

Extra package databases

bcStackYaml :: !(Path Abs File)

Location of the stack.yaml file.

Note: if the STACK_YAML environment variable is used, this may be different from bcRoot / "stack.yaml"

bcFlags :: !PackageFlags

Per-package flag overrides

bcImplicitGlobal :: !Bool

Are we loading from the implicit global stack.yaml? This is useful for providing better error messages.

bcGHCVariant :: !GHCVariant

The variant of GHC used to select a GHC bindist.

bcRoot :: BuildConfig -> Path Abs Dir Source

Directory containing the project's stack.yaml file

bcWorkDir :: (MonadReader env m, HasConfig env) => BuildConfig -> m (Path Abs Dir) Source

"bcRoot/.stack-work"

class HasConfig env => HasBuildConfig env where Source

Class for environment values that can provide a BuildConfig.

GHCVariant & HasGHCVariant

data GHCVariant Source

Specialized bariant of GHC (e.g. libgmp4 or integer-simple)

Constructors

GHCStandard

Standard bindist

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.

class HasGHCVariant env where Source

Class for environment values which have a GHCVariant

Minimal complete definition

Nothing

snapshotsDir :: (MonadReader env m, HasEnvConfig env, MonadThrow m) => m (Path Abs Dir) Source

Directory containing snapshots

Constraint synonym for use with StackMini

type StackMiniM r m = (MonadReader r m, MonadIO m, MonadBaseControl IO m, MonadLoggerIO m, MonadMask m) Source

Constraint synonym for constraints satisfied by a MiniConfig environment.

EnvConfig & HasEnvConfig

data EnvConfig Source

Configuration after the environment has been setup.

Constructors

EnvConfig 

Fields

envConfigBuildConfig :: !BuildConfig
 
envConfigCabalVersion :: !Version

This is the version of Cabal that stack will use to compile Setup.hs files in the build process.

Note that this is not necessarily the same version as the one that stack depends on as a library and which is displayed when running stack list-dependencies | grep Cabal in the stack project.

envConfigCompilerVersion :: !CompilerVersion
 
envConfigCompilerBuild :: !CompilerBuild
 
envConfigPackagesRef :: !(IORef (Maybe (Map (Path Abs Dir) TreatLikeExtraDep)))

Cache for getLocalPackages.

getCompilerPath :: (MonadIO m, MonadThrow m, MonadReader env m, HasConfig env) => WhichCompiler -> m (Path Abs File) Source

Get the path for the given compiler ignoring any local binaries.

https://github.com/commercialhaskell/stack/issues/1052

Details

ApplyGhcOptions

data ApplyGhcOptions Source

Which packages do ghc-options on the command line apply to?

Constructors

AGOTargets

all local targets

AGOLocals

all local packages, even non-targets

AGOEverything

every package

ConfigException

WhichSolverCmd

ConfigMonoid

data ConfigMonoid Source

Constructors

ConfigMonoid 

Fields

configMonoidStackRoot :: !(First (Path Abs Dir))

See: configStackRoot

configMonoidWorkDir :: !(First (Path Rel Dir))

See: configWorkDir.

configMonoidBuildOpts :: !BuildOptsMonoid

build options.

configMonoidDockerOpts :: !DockerOptsMonoid

Docker options.

configMonoidNixOpts :: !NixOptsMonoid

Options for the execution environment (nix-shell or container)

configMonoidConnectionCount :: !(First Int)

See: configConnectionCount

configMonoidHideTHLoading :: !(First Bool)

See: configHideTHLoading

configMonoidLatestSnapshotUrl :: !(First Text)

Deprecated in favour of urlsMonoidLatestSnapshot

configMonoidUrls :: !UrlsMonoid

See: 'configUrls

configMonoidPackageIndices :: !(First [PackageIndex])

See: configPackageIndices

configMonoidSystemGHC :: !(First Bool)

See: configSystemGHC

configMonoidInstallGHC :: !(First Bool)

See: configInstallGHC

configMonoidSkipGHCCheck :: !(First Bool)

See: configSkipGHCCheck

configMonoidSkipMsys :: !(First Bool)

See: configSkipMsys

configMonoidCompilerCheck :: !(First VersionCheck)

See: configCompilerCheck

configMonoidRequireStackVersion :: !IntersectingVersionRange

See: configRequireStackVersion

configMonoidArch :: !(First String)

Used for overriding the platform

configMonoidGHCVariant :: !(First GHCVariant)

Used for overriding the platform

configMonoidGHCBuild :: !(First CompilerBuild)

Used for overriding the GHC build

configMonoidJobs :: !(First Int)

See: configJobs

configMonoidExtraIncludeDirs :: !(Set (Path Abs Dir))

See: configExtraIncludeDirs

configMonoidExtraLibDirs :: !(Set (Path Abs Dir))

See: configExtraLibDirs

configMonoidOverrideGccPath :: !(First (Path Abs File))

Allow users to override the path to gcc

configMonoidConcurrentTests :: !(First Bool)

See: configConcurrentTests

configMonoidLocalBinPath :: !(First FilePath)

Used to override the binary installation dir

configMonoidImageOpts :: !ImageOptsMonoid

Image creation options.

configMonoidTemplateParameters :: !(Map Text Text)

Template parameters.

configMonoidScmInit :: !(First SCM)

Initialize SCM (e.g. git init) when making new projects?

configMonoidGhcOptions :: !GhcOptions

See configGhcOptions

configMonoidExtraPath :: ![Path Abs Dir]

Additional paths to search for executables in

configMonoidSetupInfoLocations :: ![SetupInfoLocation]

Additional setup info (inline or remote) to use for installing tools

configMonoidLocalProgramsBase :: !(First (Path Abs Dir))

Override the default local programs dir, where e.g. GHC is installed.

configMonoidPvpBounds :: !(First PvpBounds)

See configPvpBounds

configMonoidModifyCodePage :: !(First Bool)

See configModifyCodePage

configMonoidExplicitSetupDeps :: !(Map (Maybe PackageName) Bool)

See configExplicitSetupDeps

configMonoidRebuildGhcOptions :: !(First Bool)

See configMonoidRebuildGhcOptions

configMonoidApplyGhcOptions :: !(First ApplyGhcOptions)

See configApplyGhcOptions

configMonoidAllowNewer :: !(First Bool)

See configMonoidAllowNewer

configMonoidDefaultTemplate :: !(First TemplateName)

The default template to use when none is specified. (If Nothing, the default default is used.)

configMonoidAllowDifferentUser :: !(First Bool)

Allow users other than the stack root owner to use the stack installation.

configMonoidDumpLogs :: !(First DumpLogs)

See configDumpLogs

DumpLogs

data DumpLogs Source

Which build log files to dump

Constructors

DumpNoLogs

don't dump any logfiles

DumpWarningLogs

dump logfiles containing warnings

DumpAllLogs

dump all logfiles

EnvSettings

data EnvSettings Source

Controls which version of the environment is used

Constructors

EnvSettings 

Fields

esIncludeLocals :: !Bool

include local project bin directory, GHC_PACKAGE_PATH, etc

esIncludeGhcPackagePath :: !Bool

include the GHC_PACKAGE_PATH variable

esStackExe :: !Bool

set the STACK_EXE variable to the current executable name

esLocaleUtf8 :: !Bool

set the locale to C.UTF-8

GlobalOpts & GlobalOptsMonoid

data GlobalOpts Source

Parsed global command-line options.

Constructors

GlobalOpts 

Fields

globalReExecVersion :: !(Maybe String)

Expected re-exec in container version

globalDockerEntrypoint :: !(Maybe DockerEntrypoint)

Data used when stack is acting as a Docker entrypoint (internal use only)

globalLogLevel :: !LogLevel

Log level

globalTimeInLog :: !Bool

Whether to include timings in logs.

globalConfigMonoid :: !ConfigMonoid

Config monoid, for passing into loadConfig

globalResolver :: !(Maybe AbstractResolver)

Resolver override

globalCompiler :: !(Maybe CompilerVersion)

Compiler override

globalTerminal :: !Bool

We're in a terminal?

globalColorWhen :: !ColorWhen

When to use ansi terminal colors

globalStackYaml :: !(Maybe FilePath)

Override project stack.yaml

data GlobalOptsMonoid Source

Parsed global command-line options monoid.

Constructors

GlobalOptsMonoid 

Fields

globalMonoidReExecVersion :: !(First String)

Expected re-exec in container version

globalMonoidDockerEntrypoint :: !(First DockerEntrypoint)

Data used when stack is acting as a Docker entrypoint (internal use only)

globalMonoidLogLevel :: !(First LogLevel)

Log level

globalMonoidTimeInLog :: !(First Bool)

Whether to include timings in logs.

globalMonoidConfigMonoid :: !ConfigMonoid

Config monoid, for passing into loadConfig

globalMonoidResolver :: !(First AbstractResolver)

Resolver override

globalMonoidCompiler :: !(First CompilerVersion)

Compiler override

globalMonoidTerminal :: !(First Bool)

We're in a terminal?

globalMonoidColorWhen :: !(First ColorWhen)

When to use ansi colors

globalMonoidStackYaml :: !(First FilePath)

Override project stack.yaml

defaultLogLevel :: LogLevel Source

Default logging level should be something useful but not crazy.

LoadConfig

data LoadConfig m Source

Value returned by loadConfig.

Constructors

LoadConfig 

Fields

lcConfig :: !Config

Top-level Stack configuration.

lcLoadBuildConfig :: !(Maybe CompilerVersion -> m BuildConfig)

Action to load the remaining BuildConfig.

lcProjectRoot :: !(Maybe (Path Abs Dir))

The project root directory, if in a project.

PackageEntry & PackageLocation

type TreatLikeExtraDep = Bool Source

Should a package be treated just like an extra-dep?

True means, it will only be built as a dependency for others, and its test suite/benchmarks will not be run.

Useful modifying an upstream package, see: https://github.com/commercialhaskell/stack/issues/219 https://github.com/commercialhaskell/stack/issues/386

data PackageLocation Source

Constructors

PLFilePath FilePath

Note that we use FilePath and not Paths. The goal is: first parse the value raw, and then use canonicalizePath and parseAbsDir.

PLRemote Text RemotePackageType

URL and further details

PackageIndex, IndexName & IndexLocation

data PackageIndex Source

Information on a single package index

Constructors

PackageIndex 

Fields

indexName :: !IndexName
 
indexLocation :: !IndexLocation
 
indexDownloadPrefix :: !Text

URL prefix for downloading packages

indexGpgVerify :: !Bool

GPG-verify the package index during download. Only applies to Git repositories for now.

indexRequireHashes :: !Bool

Require that hashes and package size information be available for packages in this index

data IndexLocation Source

Location of the package index. This ensures that at least one of Git or HTTP is available.

Constructors

ILGit !Text 
ILHttp !Text 
ILGitHttp !Text !Text 

configPackageIndex :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File) Source

Location of the 00-index.tar file

configPackageIndexCache :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File) Source

Location of the 00-index.cache file

configPackageIndexGz :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs File) Source

Location of the 00-index.tar.gz file

configPackageIndexRoot :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Path Abs Dir) Source

Root for a specific package index

configPackageIndexRepo :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> m (Maybe (Path Abs Dir)) Source

Git repo directory for a specific package index, returns Nothing if not a Git repo

configPackageTarball :: (MonadReader env m, HasConfig env, MonadThrow m) => IndexName -> PackageIdentifier -> m (Path Abs File) Source

Location of a package tarball

Project & ProjectAndConfigMonoid

data Project Source

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

projectUserMsg :: !(Maybe String)

A warning message to display to the user when the auto generated config may have issues.

projectPackages :: ![PackageEntry]

Components of the package list

projectExtraDeps :: !(Map PackageName Version)

Components of the package list referring to package/version combos, see: https://github.com/fpco/stack/issues/41

projectFlags :: !PackageFlags

Per-package flag overrides

projectResolver :: !Resolver

How we resolve which dependencies to use

projectCompiler :: !(Maybe CompilerVersion)

When specified, overrides which compiler to use

projectExtraPackageDBs :: ![FilePath]
 

PvpBounds

ColorWhen

SCM

data SCM Source

A software control system.

Constructors

Git 

CustomSnapshot

GhcOptions

PackageFlags

Paths

bindirSuffix :: Path Rel Dir Source

Suffix applied to an installation root to get the bin dir

configInstalledCache :: (HasBuildConfig env, MonadReader env m) => m (Path Abs File) Source

File containing the installed cache, see Stack.PackageDump

configMiniBuildPlanCache :: (MonadThrow m, MonadReader env m, HasConfig env, HasGHCVariant env) => SnapName -> m (Path Abs File) Source

Where to store mini build plan caches

getProjectWorkDir :: (HasBuildConfig env, MonadReader env m) => m (Path Abs Dir) Source

Per-project work dir

docDirSuffix :: Path Rel Dir Source

Suffix applied to an installation root to get the doc dir

flagCacheLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source

Directory for holding flag cache information

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

hpcReportDir :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source

Where HPC reports and tix files get stored.

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

hoogleRoot :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source

Hoogle directory.

hoogleDatabasePath :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs File) Source

Get the hoogle database path.

packageDatabaseDeps :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source

Package database for installing dependencies into

packageDatabaseExtra :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m [Path Abs Dir] Source

Extra package databases

packageDatabaseLocal :: (MonadThrow m, MonadReader env m, HasEnvConfig env) => m (Path Abs Dir) Source

Package database for installing local packages into

platformOnlyRelDir :: (MonadReader env m, HasPlatform env, MonadThrow m) => m (Path Rel Dir) Source

Relative directory for the platform identifier

platformGhcRelDir :: (MonadReader env m, HasEnvConfig env, MonadThrow m) => m (Path Rel Dir) Source

Relative directory for the platform and GHC identifier

useShaPathOnWindows :: MonadThrow m => Path Rel Dir -> m (Path Rel Dir) Source

This is an attempt to shorten stack paths on Windows to decrease our chances of hitting 260 symbol path limit. The idea is to calculate SHA1 hash of the path used on other architectures, encode with base 16 and take first 8 symbols of it.

getWorkDir :: (MonadReader env m, HasConfig env) => m (Path Rel Dir) Source

".stack-work"

Command-specific types

Eval

data EvalOpts Source

Constructors

EvalOpts 

Instances

Exec

data ExecOpts Source

Constructors

ExecOpts 

Instances

Setup

data DownloadInfo Source

Build of the compiler distribution (e.g. standard, gmp4, tinfo6) | Information for a file to download.

data SetupInfo Source

Instances

Show SetupInfo Source 
Monoid SetupInfo Source

For siGHCs and siGHCJSs fields maps are deeply merged. For all fields the values from the last SetupInfo win.

FromJSON (WithJSONWarnings SetupInfo) Source 

Docker entrypoint

data DockerEntrypoint Source

Data passed into Docker container for the Docker entrypoint's use

Constructors

DockerEntrypoint 

Fields

deUser :: !(Maybe DockerUser)

UIDGIDetc of host user, if we wish to perform UID/GID switch in container

data DockerUser Source

Docker host user info

Constructors

DockerUser 

Fields

duUid :: UserID

uid

duGid :: GroupID

gid

duGroups :: [GroupID]

Supplemantal groups

duUmask :: FileMode

File creation mask }