| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.Setup
Contents
Synopsis
- setupEnv :: NeedTargets -> BuildOptsCLI -> Maybe Text -> RIO BuildConfig EnvConfig
 - ensureCompilerAndMsys :: (HasBuildConfig env, HasGHCVariant env) => SetupOpts -> RIO env (CompilerPaths, ExtraDirs)
 - ensureDockerStackExe :: HasConfig env => Platform -> RIO env (Path Abs File)
 - data SetupOpts = SetupOpts {
- soptsInstallIfMissing :: !Bool
 - soptsUseSystem :: !Bool
 - soptsWantedCompiler :: !WantedCompiler
 - soptsCompilerCheck :: !VersionCheck
 - soptsStackYaml :: !(Maybe (Path Abs File))
 - soptsForceReinstall :: !Bool
 - soptsSanityCheck :: !Bool
 - soptsSkipGhcCheck :: !Bool
 - soptsSkipMsys :: !Bool
 - soptsResolveMissingGHC :: !(Maybe Text)
 - soptsGHCBindistURL :: !(Maybe String)
 
 - defaultSetupInfoYaml :: String
 - withNewLocalBuildTargets :: HasEnvConfig env => [Text] -> RIO env a -> RIO env a
 - data StackReleaseInfo
 - getDownloadVersion :: StackReleaseInfo -> Maybe Version
 - stackVersion :: Version
 - preferredPlatforms :: (MonadReader env m, HasPlatform env, MonadThrow m) => m [(Bool, String)]
 - downloadStackReleaseInfo :: (MonadIO m, MonadThrow m) => Maybe String -> Maybe String -> Maybe String -> m StackReleaseInfo
 - downloadStackExe :: HasConfig env => [(Bool, String)] -> StackReleaseInfo -> Path Abs Dir -> Bool -> (Path Abs File -> IO ()) -> RIO env ()
 
Documentation
Arguments
| :: NeedTargets | |
| -> BuildOptsCLI | |
| -> Maybe Text | Message to give user when necessary GHC is not available  | 
| -> RIO BuildConfig EnvConfig | 
Modify the environment variables (like PATH) appropriately, possibly doing installation too
ensureCompilerAndMsys :: (HasBuildConfig env, HasGHCVariant env) => SetupOpts -> RIO env (CompilerPaths, ExtraDirs) Source #
Ensure both the compiler and the msys toolchain are installed and provide the PATHs to add if necessary
ensureDockerStackExe :: HasConfig env => Platform -> RIO env (Path Abs File) Source #
Ensure Docker container-compatible stack executable is downloaded
Constructors
| SetupOpts | |
Fields 
  | |
defaultSetupInfoYaml :: String Source #
Default location of the stack-setup.yaml file
withNewLocalBuildTargets :: HasEnvConfig env => [Text] -> RIO env a -> RIO env a Source #
Some commands (script, ghci and exec) set targets dynamically see also the note about only local targets for rebuildEnv
Stack binary download
data StackReleaseInfo Source #
stackVersion :: Version Source #
Current Stack version
preferredPlatforms :: (MonadReader env m, HasPlatform env, MonadThrow m) => m [(Bool, String)] Source #
downloadStackReleaseInfo Source #
Arguments
| :: (MonadIO m, MonadThrow m) | |
| => Maybe String | |
| -> Maybe String | |
| -> Maybe String | optional version  | 
| -> m StackReleaseInfo |