stack-2.1.1.1: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.Types.Config

Contents

Description

The Config type.

Synopsis

Main configuration types and classes

HasPlatform & HasStackRoot

data PlatformVariant Source #

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

Runner

class (HasProcessContext env, HasLogFunc env) => HasRunner env where Source #

Class for environment values which have a Runner.

Methods

runnerL :: Lens' env Runner Source #

Instances
HasRunner EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasRunner BuildConfig Source # 
Instance details

Defined in Stack.Types.Config

HasRunner Config Source # 
Instance details

Defined in Stack.Types.Config

HasRunner Runner Source # 
Instance details

Defined in Stack.Types.Config

data Runner Source #

The base environment that almost everything in Stack runs in, based off of parsing command line options in GlobalOpts. Provides logging and process execution.

data ColorWhen Source #

Instances
Eq ColorWhen Source # 
Instance details

Defined in Stack.Types.Config

Show ColorWhen Source # 
Instance details

Defined in Stack.Types.Config

Generic ColorWhen Source # 
Instance details

Defined in Stack.Types.Config

Associated Types

type Rep ColorWhen :: Type -> Type #

FromJSON ColorWhen Source # 
Instance details

Defined in Stack.Types.Config

type Rep ColorWhen Source # 
Instance details

Defined in Stack.Types.Config

type Rep ColorWhen = D1 (MetaData "ColorWhen" "Stack.Types.Config" "stack-2.1.1.1-IcmSiv90ky67Jq7jcJ1Q2" False) (C1 (MetaCons "ColorNever" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ColorAlways" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ColorAuto" PrefixI False) (U1 :: Type -> Type)))

Config & HasConfig

data Config Source #

The top-level Stackage configuration.

Constructors

Config 

Fields

class (HasPlatform env, HasGHCVariant env, HasProcessContext env, HasPantryConfig env, HasTerm env, HasRunner env) => HasConfig env where Source #

Class for environment values that can provide a Config.

Minimal complete definition

Nothing

Instances
HasConfig EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasConfig BuildConfig Source # 
Instance details

Defined in Stack.Types.Config

HasConfig Config Source # 
Instance details

Defined in Stack.Types.Config

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

configProjectRoot :: Config -> Maybe (Path Abs Dir) Source #

The project root directory, if in a project.

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.

These are the components which know nothing about local configuration.

Constructors

BuildConfig 

Fields

data ProjectPackage Source #

A view of a project package needed for resolving components

data DepPackage Source #

A view of a dependency package, specified in stack.yaml

Constructors

DepPackage 

Fields

ppRoot :: ProjectPackage -> Path Abs Dir Source #

Root directory for the given ProjectPackage

ppVersion :: MonadIO m => ProjectPackage -> m Version Source #

Version for the given 'ProjectPackage

ppComponents :: MonadIO m => ProjectPackage -> m (Set NamedComponent) Source #

All components available in the given ProjectPackage

projectRootL :: HasBuildConfig env => Getting r env (Path Abs Dir) Source #

Directory containing the project's stack.yaml file

class HasConfig env => HasBuildConfig env where Source #

Minimal complete definition

Nothing

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

EnvConfig & HasEnvConfig

data EnvConfig Source #

Configuration after the environment has been setup.

Instances
HasPantryConfig EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasProcessContext EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasLogFunc EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasTerm EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasStylesUpdate EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasSourceMap EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasCompiler EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasEnvConfig EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasBuildConfig EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasConfig EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasRunner EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasGHCVariant EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

HasPlatform EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

class HasSourceMap env where Source #

Instances
HasSourceMap EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

class (HasBuildConfig env, HasSourceMap env, HasCompiler env) => HasEnvConfig env where Source #

Instances
HasEnvConfig EnvConfig Source # 
Instance details

Defined in Stack.Types.Config

getCompilerPath :: HasCompiler env => RIO env (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

Instances
Bounded ApplyGhcOptions Source # 
Instance details

Defined in Stack.Types.Config

Enum ApplyGhcOptions Source # 
Instance details

Defined in Stack.Types.Config

Eq ApplyGhcOptions Source # 
Instance details

Defined in Stack.Types.Config

Ord ApplyGhcOptions Source # 
Instance details

Defined in Stack.Types.Config

Read ApplyGhcOptions Source # 
Instance details

Defined in Stack.Types.Config

Show ApplyGhcOptions Source # 
Instance details

Defined in Stack.Types.Config

FromJSON ApplyGhcOptions Source # 
Instance details

Defined in Stack.Types.Config

CabalConfigKey

data CabalConfigKey Source #

Which packages do configure opts apply to?

Constructors

CCKTargets

See AGOTargets

CCKLocals

See AGOLocals

CCKEverything

See AGOEverything

CCKPackage !PackageName

A specific package

ConfigException

ConfigMonoid

data ConfigMonoid Source #

Constructors

ConfigMonoid 

Fields

Instances
Show ConfigMonoid Source # 
Instance details

Defined in Stack.Types.Config

Generic ConfigMonoid Source # 
Instance details

Defined in Stack.Types.Config

Associated Types

type Rep ConfigMonoid :: Type -> Type #

Semigroup ConfigMonoid Source # 
Instance details

Defined in Stack.Types.Config

Monoid ConfigMonoid Source # 
Instance details

Defined in Stack.Types.Config

type Rep ConfigMonoid Source # 
Instance details

Defined in Stack.Types.Config

type Rep ConfigMonoid = D1 (MetaData "ConfigMonoid" "Stack.Types.Config" "stack-2.1.1.1-IcmSiv90ky67Jq7jcJ1Q2" False) (C1 (MetaCons "ConfigMonoid" PrefixI True) (((((S1 (MetaSel (Just "configMonoidStackRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First (Path Abs Dir))) :*: (S1 (MetaSel (Just "configMonoidWorkDir") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First (Path Rel Dir))) :*: S1 (MetaSel (Just "configMonoidBuildOpts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BuildOptsMonoid))) :*: (S1 (MetaSel (Just "configMonoidDockerOpts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DockerOptsMonoid) :*: (S1 (MetaSel (Just "configMonoidNixOpts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 NixOptsMonoid) :*: S1 (MetaSel (Just "configMonoidConnectionCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Int))))) :*: ((S1 (MetaSel (Just "configMonoidHideTHLoading") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstTrue) :*: (S1 (MetaSel (Just "configMonoidLatestSnapshot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Text)) :*: S1 (MetaSel (Just "configMonoidPackageIndices") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First [HackageSecurityConfig])))) :*: (S1 (MetaSel (Just "configMonoidSystemGHC") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Bool)) :*: (S1 (MetaSel (Just "configMonoidInstallGHC") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstTrue) :*: S1 (MetaSel (Just "configMonoidSkipGHCCheck") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstFalse))))) :*: (((S1 (MetaSel (Just "configMonoidSkipMsys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstFalse) :*: (S1 (MetaSel (Just "configMonoidCompilerCheck") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First VersionCheck)) :*: S1 (MetaSel (Just "configMonoidCompilerRepository") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First CompilerRepository)))) :*: (S1 (MetaSel (Just "configMonoidRequireStackVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IntersectingVersionRange) :*: (S1 (MetaSel (Just "configMonoidArch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First String)) :*: S1 (MetaSel (Just "configMonoidGHCVariant") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First GHCVariant))))) :*: ((S1 (MetaSel (Just "configMonoidGHCBuild") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First CompilerBuild)) :*: (S1 (MetaSel (Just "configMonoidJobs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Int)) :*: S1 (MetaSel (Just "configMonoidExtraIncludeDirs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [FilePath]))) :*: (S1 (MetaSel (Just "configMonoidExtraLibDirs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [FilePath]) :*: (S1 (MetaSel (Just "configMonoidOverrideGccPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First (Path Abs File))) :*: S1 (MetaSel (Just "configMonoidOverrideHpack") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First FilePath))))))) :*: ((((S1 (MetaSel (Just "configMonoidConcurrentTests") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Bool)) :*: (S1 (MetaSel (Just "configMonoidLocalBinPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First FilePath)) :*: S1 (MetaSel (Just "configMonoidTemplateParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map Text Text)))) :*: (S1 (MetaSel (Just "configMonoidScmInit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First SCM)) :*: (S1 (MetaSel (Just "configMonoidGhcOptionsByName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MonoidMap PackageName (Dual [Text]))) :*: S1 (MetaSel (Just "configMonoidGhcOptionsByCat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MonoidMap ApplyGhcOptions (Dual [Text])))))) :*: ((S1 (MetaSel (Just "configMonoidCabalConfigOpts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MonoidMap CabalConfigKey (Dual [Text]))) :*: (S1 (MetaSel (Just "configMonoidExtraPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Path Abs Dir]) :*: S1 (MetaSel (Just "configMonoidSetupInfoLocations") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [SetupInfoLocation]))) :*: (S1 (MetaSel (Just "configMonoidLocalProgramsBase") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First (Path Abs Dir))) :*: (S1 (MetaSel (Just "configMonoidPvpBounds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First PvpBounds)) :*: S1 (MetaSel (Just "configMonoidModifyCodePage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstTrue))))) :*: (((S1 (MetaSel (Just "configMonoidExplicitSetupDeps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map (Maybe PackageName) Bool)) :*: (S1 (MetaSel (Just "configMonoidRebuildGhcOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstFalse) :*: S1 (MetaSel (Just "configMonoidApplyGhcOptions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First ApplyGhcOptions)))) :*: (S1 (MetaSel (Just "configMonoidAllowNewer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Bool)) :*: (S1 (MetaSel (Just "configMonoidDefaultTemplate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First TemplateName)) :*: S1 (MetaSel (Just "configMonoidAllowDifferentUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Bool))))) :*: ((S1 (MetaSel (Just "configMonoidDumpLogs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First DumpLogs)) :*: (S1 (MetaSel (Just "configMonoidSaveHackageCreds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Bool)) :*: S1 (MetaSel (Just "configMonoidHackageBaseUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Text)))) :*: ((S1 (MetaSel (Just "configMonoidColorWhen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First ColorWhen)) :*: S1 (MetaSel (Just "configMonoidStyles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 StylesUpdate)) :*: (S1 (MetaSel (Just "configMonoidHideSourcePaths") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstTrue) :*: S1 (MetaSel (Just "configMonoidRecommendUpgrade") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstTrue))))))))

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

Instances
Bounded DumpLogs Source # 
Instance details

Defined in Stack.Types.Config

Enum DumpLogs Source # 
Instance details

Defined in Stack.Types.Config

Eq DumpLogs Source # 
Instance details

Defined in Stack.Types.Config

Ord DumpLogs Source # 
Instance details

Defined in Stack.Types.Config

Read DumpLogs Source # 
Instance details

Defined in Stack.Types.Config

Show DumpLogs Source # 
Instance details

Defined in Stack.Types.Config

FromJSON DumpLogs Source # 
Instance details

Defined in Stack.Types.Config

EnvSettings

data EnvSettings Source #

Controls which version of the environment is used

Constructors

EnvSettings 

Fields

defaultEnvSettings :: EnvSettings Source #

Default EnvSettings which includes locals and GHC_PACKAGE_PATH.

Note that this also passes through the GHCRTS environment variable. See https://github.com/commercialhaskell/stack/issues/3444

plainEnvSettings :: EnvSettings Source #

Environment settings which do not embellish the environment

Note that this also passes through the GHCRTS environment variable. See https://github.com/commercialhaskell/stack/issues/3444

GlobalOpts & GlobalOptsMonoid

data GlobalOpts Source #

Parsed global command-line options.

Constructors

GlobalOpts 

Fields

Instances
Show GlobalOpts Source # 
Instance details

Defined in Stack.Types.Config

data GlobalOptsMonoid Source #

Parsed global command-line options monoid.

Constructors

GlobalOptsMonoid 

Fields

Instances
Generic GlobalOptsMonoid Source # 
Instance details

Defined in Stack.Types.Config

Associated Types

type Rep GlobalOptsMonoid :: Type -> Type #

Semigroup GlobalOptsMonoid Source # 
Instance details

Defined in Stack.Types.Config

Monoid GlobalOptsMonoid Source # 
Instance details

Defined in Stack.Types.Config

type Rep GlobalOptsMonoid Source # 
Instance details

Defined in Stack.Types.Config

type Rep GlobalOptsMonoid = D1 (MetaData "GlobalOptsMonoid" "Stack.Types.Config" "stack-2.1.1.1-IcmSiv90ky67Jq7jcJ1Q2" False) (C1 (MetaCons "GlobalOptsMonoid" PrefixI True) (((S1 (MetaSel (Just "globalMonoidReExecVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First String)) :*: (S1 (MetaSel (Just "globalMonoidDockerEntrypoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First DockerEntrypoint)) :*: S1 (MetaSel (Just "globalMonoidLogLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First LogLevel)))) :*: (S1 (MetaSel (Just "globalMonoidTimeInLog") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FirstTrue) :*: (S1 (MetaSel (Just "globalMonoidConfigMonoid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ConfigMonoid) :*: S1 (MetaSel (Just "globalMonoidResolver") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First (Unresolved AbstractResolver)))))) :*: ((S1 (MetaSel (Just "globalMonoidResolverRoot") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First FilePath)) :*: (S1 (MetaSel (Just "globalMonoidCompiler") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First WantedCompiler)) :*: S1 (MetaSel (Just "globalMonoidTerminal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Bool)))) :*: ((S1 (MetaSel (Just "globalMonoidStyles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 StylesUpdate) :*: S1 (MetaSel (Just "globalMonoidTermWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First Int))) :*: (S1 (MetaSel (Just "globalMonoidStackYaml") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First FilePath)) :*: S1 (MetaSel (Just "globalMonoidLockFileBehavior") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (First LockFileBehavior)))))))

data StackYamlLoc Source #

Location for the project's stack.yaml file.

Constructors

SYLDefault

Use the standard parent-directory-checking logic

SYLOverride !(Path Abs File)

Use a specific stack.yaml file provided

SYLNoProject ![PackageIdentifierRevision]

Do not load up a project, just user configuration. Include the given extra dependencies with the resolver.

SYLGlobalProject

Do not look for a project configuration, and use the implicit global.

Instances
Show StackYamlLoc Source # 
Instance details

Defined in Stack.Types.Config

data LockFileBehavior Source #

How to interact with lock files

Constructors

LFBReadWrite

Read and write lock files

LFBReadOnly

Read lock files, but do not write them

LFBIgnore

Entirely ignore lock files

LFBErrorOnWrite

Error out on trying to write a lock file. This can be used to ensure that lock files in a repository already ensure reproducible builds.

defaultLogLevel :: LogLevel Source #

Default logging level should be something useful but not crazy.

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

Instances
Show Project Source # 
Instance details

Defined in Stack.Types.Config

ToJSON Project Source # 
Instance details

Defined in Stack.Types.Config

data ProjectConfig a Source #

Project configuration information. Not every run of Stack has a true local project; see constructors below.

Constructors

PCProject a

Normal run: we want a project, and have one. This comes from either SYLDefault or SYLOverride.

PCGlobalProject

No project was found when using SYLDefault. Instead, use the implicit global.

PCNoProject ![PackageIdentifierRevision]

Use a no project run. This comes from SYLNoProject.

data Curator Source #

Extra configuration intended exclusively for usage by the curator tool. In other words, this is not part of the documented and exposed Stack API. SUBJECT TO CHANGE.

PvpBounds

data PvpBoundsType Source #

How PVP bounds should be added to .cabal files

Instances
Bounded PvpBoundsType Source # 
Instance details

Defined in Stack.Types.Config

Enum PvpBoundsType Source # 
Instance details

Defined in Stack.Types.Config

Eq PvpBoundsType Source # 
Instance details

Defined in Stack.Types.Config

Ord PvpBoundsType Source # 
Instance details

Defined in Stack.Types.Config

Read PvpBoundsType Source # 
Instance details

Defined in Stack.Types.Config

Show PvpBoundsType Source # 
Instance details

Defined in Stack.Types.Config

ColorWhen

Styles

SCM

data SCM Source #

A software control system.

Constructors

Git 
Instances
Show SCM Source # 
Instance details

Defined in Stack.Types.Config

Methods

showsPrec :: Int -> SCM -> ShowS #

show :: SCM -> String #

showList :: [SCM] -> ShowS #

ToJSON SCM Source # 
Instance details

Defined in Stack.Types.Config

FromJSON SCM Source # 
Instance details

Defined in Stack.Types.Config

Paths

bindirSuffix :: Path Rel Dir Source #

Suffix applied to an installation root to get the bin dir

data GlobalInfoSource Source #

Where do we get information on global packages for loading up a LoadedSnapshot?

Constructors

GISSnapshotHints

Accept the hints in the snapshot definition

GISCompiler ActualCompiler

Look up the actual information in the installed compiler

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

extraBinDirs :: HasEnvConfig env => RIO env (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 :: HasEnvConfig env => RIO env (Path Abs Dir) Source #

Where HPC reports and tix files get stored.

installationRootDeps :: HasEnvConfig env => RIO env (Path Abs Dir) Source #

Installation root for dependencies

installationRootLocal :: HasEnvConfig env => RIO env (Path Abs Dir) Source #

Installation root for locals

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

Installation root for compiler tools

hoogleRoot :: HasEnvConfig env => RIO env (Path Abs Dir) Source #

Hoogle directory.

hoogleDatabasePath :: HasEnvConfig env => RIO env (Path Abs File) Source #

Get the hoogle database path.

packageDatabaseDeps :: HasEnvConfig env => RIO env (Path Abs Dir) Source #

Package database for installing dependencies into

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

Extra package databases

packageDatabaseLocal :: HasEnvConfig env => RIO env (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

platformGhcVerOnlyRelDir :: (MonadReader env m, HasPlatform env, HasGHCVariant env, MonadThrow m) => m (Path Rel Dir) Source #

Relative directory for the platform and GHC identifier without GHC bindist build

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.

shaPath :: (IsPath Rel t, MonadThrow m) => Path Rel t -> m (Path Rel t) Source #

shaPathForBytes :: (IsPath Rel t, MonadThrow m) => ByteString -> m (Path Rel t) Source #

workDirL :: HasConfig env => Lens' env (Path Rel Dir) Source #

".stack-work"

Command-specific types

Eval

data EvalOpts Source #

Constructors

EvalOpts 
Instances
Show EvalOpts Source # 
Instance details

Defined in Stack.Types.Config

Exec

data ExecOpts Source #

Constructors

ExecOpts 
Instances
Show ExecOpts Source # 
Instance details

Defined in Stack.Types.Config

Setup

data DownloadInfo Source #

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

Docker entrypoint

newtype DockerEntrypoint Source #

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

Constructors

DockerEntrypoint 

Fields

data DockerUser Source #

Docker host user info

Constructors

DockerUser 

Fields

Lens helpers

wantedCompilerVersionL :: HasBuildConfig s => Getting r s WantedCompiler Source #

The compiler specified by the SnapshotDef. This may be different from the actual compiler used!

actualCompilerVersionL :: HasSourceMap env => SimpleGetter env ActualCompiler Source #

The version of the compiler which will actually be used. May be different than that specified in the SnapshotDef and returned by wantedCompilerVersionL.

class HasCompiler env where Source #

An environment which ensures that the given compiler is available on the PATH

data CompilerPaths Source #

Paths on the filesystem for the compiler we're using

Constructors

CompilerPaths 

Fields

newtype GhcPkgExe Source #

Location of the ghc-pkg executable

Constructors

GhcPkgExe (Path Abs File) 
Instances
Show GhcPkgExe Source # 
Instance details

Defined in Stack.Types.Config

getGhcPkgExe :: HasCompiler env => RIO env GhcPkgExe Source #

Get the GhcPkgExe from a HasCompiler environment

data ExtraDirs Source #

Constructors

ExtraDirs 

Fields

Instances
Show ExtraDirs Source # 
Instance details

Defined in Stack.Types.Config

Generic ExtraDirs Source # 
Instance details

Defined in Stack.Types.Config

Associated Types

type Rep ExtraDirs :: Type -> Type #

Semigroup ExtraDirs Source # 
Instance details

Defined in Stack.Types.Config

Monoid ExtraDirs Source # 
Instance details

Defined in Stack.Types.Config

type Rep ExtraDirs Source # 
Instance details

Defined in Stack.Types.Config

type Rep ExtraDirs = D1 (MetaData "ExtraDirs" "Stack.Types.Config" "stack-2.1.1.1-IcmSiv90ky67Jq7jcJ1Q2" False) (C1 (MetaCons "ExtraDirs" PrefixI True) (S1 (MetaSel (Just "edBins") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Path Abs Dir]) :*: (S1 (MetaSel (Just "edInclude") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Path Abs Dir]) :*: S1 (MetaSel (Just "edLib") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Path Abs Dir]))))

Lens reexport

view :: MonadReader s m => Getting a s a -> m a #

to :: (s -> a) -> SimpleGetter s a #

to creates a getter from any function:

a ^. to f = f a

It's most useful in chains, because it lets you mix lenses and ordinary functions. Suppose you have a record which comes from some third-party library and doesn't have any lens accessors. You want to do something like this:

value ^. _1 . field . at 2

However, field isn't a getter, and you have to do this instead:

field (value ^. _1) ^. at 2

but now value is in the middle and it's hard to read the resulting code. A variant with to is prettier and more readable:

value ^. _1 . to field . at 2