| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.Setup
Contents
Synopsis
- setupEnv :: (HasBuildConfig env, HasGHCVariant env) => Maybe Text -> RIO env EnvConfig
 - ensureCompiler :: (HasConfig env, HasGHCVariant env) => SetupOpts -> RIO env (Maybe ExtraDirs, CompilerBuild, Bool)
 - ensureDockerStackExe :: HasConfig env => Platform -> RIO env (Path Abs File)
 - getSystemCompiler :: (HasProcessContext env, HasLogFunc env) => WhichCompiler -> RIO env (Maybe (CompilerVersion CVActual, Arch))
 - getCabalInstallVersion :: (HasProcessContext env, HasLogFunc env) => RIO env (Maybe Version)
 - data SetupOpts = SetupOpts {
- soptsInstallIfMissing :: !Bool
 - soptsUseSystem :: !Bool
 - soptsWantedCompiler :: !(CompilerVersion CVWanted)
 - soptsCompilerCheck :: !VersionCheck
 - soptsStackYaml :: !(Maybe (Path Abs File))
 - soptsForceReinstall :: !Bool
 - soptsSanityCheck :: !Bool
 - soptsSkipGhcCheck :: !Bool
 - soptsSkipMsys :: !Bool
 - soptsUpgradeCabal :: !(Maybe UpgradeTo)
 - soptsResolveMissingGHC :: !(Maybe Text)
 - soptsSetupInfoYaml :: !FilePath
 - soptsGHCBindistURL :: !(Maybe String)
 - soptsGHCJSBootOpts :: [String]
 
 - defaultSetupInfoYaml :: String
 - removeHaskellEnvVars :: Map Text Text -> Map Text Text
 - 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
| :: (HasBuildConfig env, HasGHCVariant env) | |
| => Maybe Text | Message to give user when necessary GHC is not available  | 
| -> RIO env EnvConfig | 
Modify the environment variables (like PATH) appropriately, possibly doing installation too
ensureCompiler :: (HasConfig env, HasGHCVariant env) => SetupOpts -> RIO env (Maybe ExtraDirs, CompilerBuild, Bool) Source #
Ensure compiler (ghc or ghcjs) is 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
getSystemCompiler :: (HasProcessContext env, HasLogFunc env) => WhichCompiler -> RIO env (Maybe (CompilerVersion CVActual, Arch)) Source #
Get the version of the system compiler, if available
getCabalInstallVersion :: (HasProcessContext env, HasLogFunc env) => RIO env (Maybe Version) Source #
Constructors
| SetupOpts | |
Fields 
  | |
defaultSetupInfoYaml :: String Source #
Default location of the stack-setup.yaml file
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 |