Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data Config = Config {
- configWorkDir :: !(Path Rel Dir)
- configUserConfigPath :: !(Path Abs File)
- configBuild :: !BuildOpts
- configDocker :: !DockerOpts
- configNix :: !NixOpts
- configProcessContextSettings :: !(EnvSettings -> IO ProcessContext)
- configLocalProgramsBase :: !(Path Abs Dir)
- configLocalPrograms :: !(Path Abs Dir)
- configHideTHLoading :: !Bool
- configPrefixTimestamps :: !Bool
- configPlatform :: !Platform
- configPlatformVariant :: !PlatformVariant
- configGHCVariant :: !(Maybe GHCVariant)
- configGHCBuild :: !(Maybe CompilerBuild)
- configLatestSnapshot :: !Text
- configSystemGHC :: !Bool
- configInstallGHC :: !Bool
- configSkipGHCCheck :: !Bool
- configSkipMsys :: !Bool
- configCompilerCheck :: !VersionCheck
- configCompilerRepository :: !CompilerRepository
- configLocalBin :: !(Path Abs Dir)
- configRequireStackVersion :: !VersionRange
- configJobs :: !Int
- configOverrideGccPath :: !(Maybe (Path Abs File))
- configExtraIncludeDirs :: ![FilePath]
- configExtraLibDirs :: ![FilePath]
- configCustomPreprocessorExts :: ![Text]
- configConcurrentTests :: !Bool
- configTemplateParams :: !(Map Text Text)
- configScmInit :: !(Maybe SCM)
- configGhcOptionsByName :: !(Map PackageName [Text])
- configGhcOptionsByCat :: !(Map ApplyGhcOptions [Text])
- configCabalConfigOpts :: !(Map CabalConfigKey [Text])
- configSetupInfoLocations :: ![String]
- configSetupInfoInline :: !SetupInfo
- configPvpBounds :: !PvpBounds
- configModifyCodePage :: !Bool
- configRebuildGhcOptions :: !Bool
- configApplyGhcOptions :: !ApplyGhcOptions
- configApplyProgOptions :: !ApplyProgOptions
- configAllowNewer :: !Bool
- configAllowNewerDeps :: !(Maybe [PackageName])
- configDefaultTemplate :: !(Maybe TemplateName)
- configAllowDifferentUser :: !Bool
- configDumpLogs :: !DumpLogs
- configProject :: !(ProjectConfig (Project, Path Abs File))
- configAllowLocals :: !Bool
- configSaveHackageCreds :: !Bool
- configHackageBaseUrl :: !Text
- configRunner :: !Runner
- configPantryConfig :: !PantryConfig
- configStackRoot :: !(Path Abs Dir)
- configResolver :: !(Maybe AbstractResolver)
- configUserStorage :: !UserStorage
- configHideSourcePaths :: !Bool
- configRecommendUpgrade :: !Bool
- configNotifyIfNixOnPath :: !Bool
- configNoRunCompile :: !Bool
- configStackDeveloperMode :: !Bool
- configCasa :: !(Maybe (CasaRepoPrefix, Int))
- class (HasPlatform env, HasGHCVariant env, HasProcessContext env, HasPantryConfig env, HasTerm env, HasRunner env) => HasConfig env where
- askLatestSnapshotUrl :: (MonadReader env m, HasConfig env) => m Text
- configProjectRoot :: Config -> Maybe (Path Abs Dir)
- ghcInstallHook :: HasConfig env => RIO env (Path Abs File)
- buildOptsL :: HasConfig s => Lens' s BuildOpts
- envOverrideSettingsL :: HasConfig env => Lens' env (EnvSettings -> IO ProcessContext)
- globalOptsL :: HasRunner env => Lens' env GlobalOpts
- stackGlobalConfigL :: HasConfig s => Lens' s (Path Abs File)
- stackRootL :: HasConfig s => Lens' s (Path Abs Dir)
- workDirL :: HasConfig env => Lens' env (Path Rel Dir)
- prettyStackDevL :: HasConfig env => [StyleDoc] -> RIO env ()
Documentation
The top-level Stackage configuration.
Config | |
|
Instances
HasPantryConfig Config Source # | |
Defined in Stack.Types.Config | |
HasLogFunc Config Source # | |
HasProcessContext Config Source # | |
Defined in Stack.Types.Config | |
HasTerm Config Source # | |
HasStylesUpdate Config Source # | |
Defined in Stack.Types.Config | |
HasConfig Config Source # | |
HasGHCVariant Config Source # | |
Defined in Stack.Types.Config | |
HasPlatform Config Source # | |
Defined in Stack.Types.Config | |
HasRunner Config Source # | |
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
.
askLatestSnapshotUrl :: (MonadReader env m, HasConfig env) => m Text Source #
Get the URL to request the information on the latest snapshots
configProjectRoot :: Config -> Maybe (Path Abs Dir) Source #
The project root directory, if in a project.
Lens helpers
envOverrideSettingsL :: HasConfig env => Lens' env (EnvSettings -> IO ProcessContext) Source #
globalOptsL :: HasRunner env => Lens' env GlobalOpts Source #