Skip to content

Commit

Permalink
Perform package resolving with modified environment #712
Browse files Browse the repository at this point in the history
This allows the Git installed by `stack setup` to be used
  • Loading branch information
snoyberg committed Aug 5, 2015
1 parent 9cb1dac commit 0f6a117
Show file tree
Hide file tree
Showing 10 changed files with 26 additions and 22 deletions.
1 change: 1 addition & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ Bug fixes:
* Extensions from the `other-extensions` field no longer enabled by default [#449](https://github.com/commercialhaskell/stack/issues/449)
* Fix: haddock forces rebuild of empty packages [#452](https://github.com/commercialhaskell/stack/issues/452)
* Don't copy over executables excluded by component selection [#605](https://github.com/commercialhaskell/stack/issues/605)
* Fix: stack fails on Windows with git package in stack.yaml and no git binary on path [#712](https://github.com/commercialhaskell/stack/issues/712)

## 0.1.2.0

Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@ withLoadPackage menv inner = do
-- | Reset the build (remove Shake database and .gen files).
clean :: (M env m) => m ()
clean = do
bconfig <- asks getBuildConfig
econfig <- asks getEnvConfig
forM_
(Map.keys (bcPackages bconfig))
(Map.keys (envConfigPackages econfig))
(distDirFromDir >=> removeTreeIfExists)
2 changes: 1 addition & 1 deletion src/Stack/Build/Coverage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ generateHpcReport pkgDir pkgName pkgId testName = do
hpcDir <- hpcDirFromDir pkgDir
hpcRelDir <- (</> dotHpc) <$> hpcRelativeDir
-- Compute arguments used for both "hpc markup" and "hpc report".
pkgDirs <- Map.keys . bcPackages <$> asks getBuildConfig
pkgDirs <- Map.keys . envConfigPackages <$> asks getEnvConfig
let args =
-- Use index files from all packages (allows cross-package
-- coverage results).
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -195,7 +195,7 @@ loadLocals bopts latestVersion = do
-- Iterate over local packages declared in stack.yaml and turn them
-- into LocalPackage structures. The targets affect whether these
-- packages will be marked as wanted.
lps <- forM (Map.toList $ bcPackages bconfig) $ \(dir, validWanted) -> do
lps <- forM (Map.toList $ envConfigPackages econfig) $ \(dir, validWanted) -> do
cabalfp <- getCabalFileName dir
name <- parsePackageNameFromFilePath cabalfp
let wanted = validWanted && isWanted' dir name
Expand Down
17 changes: 6 additions & 11 deletions src/Stack/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@
module Stack.Config
(loadConfig
,packagesParser
,resolvePackageEntry
) where

import qualified Codec.Archive.Tar as Tar
Expand Down Expand Up @@ -207,23 +208,21 @@ loadConfig configArgs mstackYaml = do
Just (_, _, projectConfig) -> configArgs : projectConfig : extraConfigs
unless (fromCabalVersion Meta.version `withinRange` configRequireStackVersion config)
(throwM (BadStackVersionException (configRequireStackVersion config)))
menv <- runReaderT getMinimalEnvOverride config
return $ LoadConfig
{ lcConfig = config
, lcLoadBuildConfig = loadBuildConfig menv mproject config stackRoot
, lcLoadBuildConfig = loadBuildConfig mproject config stackRoot
, lcProjectRoot = fmap (\(_, fp, _) -> parent fp) mproject
}

-- | Load the build configuration, adds build-specific values to config loaded by @loadConfig@.
-- values.
loadBuildConfig :: (MonadLogger m, MonadIO m, MonadCatch m, MonadReader env m, HasHttpManager env, MonadBaseControl IO m, HasTerminal env)
=> EnvOverride
-> Maybe (Project, Path Abs File, ConfigMonoid)
=> Maybe (Project, Path Abs File, ConfigMonoid)
-> Config
-> Path Abs Dir
-> Maybe AbstractResolver -- override resolver
-> m BuildConfig
loadBuildConfig menv mproject config stackRoot mresolver = do
loadBuildConfig mproject config stackRoot mresolver = do
env <- ask
let miniConfig = MiniConfig (getHttpManager env) config
(project', stackYamlFP) <- case mproject of
Expand Down Expand Up @@ -289,17 +288,13 @@ loadBuildConfig menv mproject config stackRoot mresolver = do
mbp <- runReaderT (parseCustomMiniBuildPlan stackYamlFP url) miniConfig
return $ mbpGhcVersion mbp

let root = parent stackYamlFP
packages' <- mapM (resolvePackageEntry menv root) (projectPackages project)
let packages = Map.fromList $ concat packages'

return BuildConfig
{ bcConfig = config
, bcResolver = projectResolver project
, bcGhcVersionExpected = ghcVersion
, bcPackages = packages
, bcPackageEntries = projectPackages project
, bcExtraDeps = projectExtraDeps project
, bcRoot = root
, bcRoot = parent stackYamlFP -- TODO remove this field, since it's redundant with bcStackYaml
, bcStackYaml = stackYamlFP
, bcFlags = projectFlags project
}
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Repl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@ ghciSetup targets = do
pwd <- getWorkingDir
locals <-
liftM catMaybes $
forM (M.toList (bcPackages bconfig)) $
forM (M.toList (envConfigPackages econfig)) $
\(dir,validWanted) ->
do cabalfp <- getCabalFileName dir
name <- parsePackageNameFromFilePath cabalfp
Expand Down
6 changes: 6 additions & 0 deletions src/Stack/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ import Path.IO
import Prelude -- Fix AMP warning
import Safe (headMay, readMay)
import Stack.Build.Types
import Stack.Config (resolvePackageEntry)
import Stack.Constants (distRelativeDir)
import Stack.Fetch
import Stack.GhcPkg (createDatabase, getCabalPkgVer, getGlobalDB)
Expand Down Expand Up @@ -160,10 +161,14 @@ setupEnv = do
menv <- mkEnvOverride platform env
ghcVer <- getGhcVersion menv
cabalVer <- getCabalPkgVer menv
packages <- mapM
(resolvePackageEntry menv (bcRoot bconfig))
(bcPackageEntries bconfig)
let envConfig0 = EnvConfig
{ envConfigBuildConfig = bconfig
, envConfigCabalVersion = cabalVer
, envConfigGhcVersion = ghcVer
, envConfigPackages = Map.fromList $ concat packages
}

-- extra installation bin directories
Expand Down Expand Up @@ -229,6 +234,7 @@ setupEnv = do
}
, envConfigCabalVersion = cabalVer
, envConfigGhcVersion = ghcVer
, envConfigPackages = envConfigPackages envConfig0
}

-- | Augment the PATH environment variable with the given extra paths
Expand Down
3 changes: 2 additions & 1 deletion src/Stack/Solver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -142,6 +142,7 @@ solveExtraDeps :: (MonadReader env m, HasEnvConfig env, MonadIO m, MonadMask m,
solveExtraDeps modStackYaml = do
$logInfo "This command is not guaranteed to give you a perfect build plan"
$logInfo "It's possible that even with the changes generated below, you will still need to do some manual tweaking"
econfig <- asks getEnvConfig
bconfig <- asks getBuildConfig
snapshot <-
case bcResolver bconfig of
Expand All @@ -164,7 +165,7 @@ solveExtraDeps modStackYaml = do
(Map.toList packages)

(_ghc, extraDeps) <- cabalSolver
(Map.keys $ bcPackages bconfig)
(Map.keys $ envConfigPackages econfig)
constraints

let newDeps = extraDeps `Map.difference` packages
Expand Down
5 changes: 3 additions & 2 deletions src/Stack/Types/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -225,7 +225,7 @@ data BuildConfig = BuildConfig
-- packages.
, bcGhcVersionExpected :: !Version
-- ^ Version of GHC we expected for this build
, bcPackages :: !(Map (Path Abs Dir) Bool)
, bcPackageEntries :: ![PackageEntry]
-- ^ Local packages identified by a path, Bool indicates whether it is
-- a non-dependency (the opposite of 'peExtraDep')
, bcExtraDeps :: !(Map PackageName Version)
Expand All @@ -248,7 +248,8 @@ data BuildConfig = BuildConfig
data EnvConfig = EnvConfig
{envConfigBuildConfig :: !BuildConfig
,envConfigCabalVersion :: !Version
,envConfigGhcVersion :: !Version}
,envConfigGhcVersion :: !Version
,envConfigPackages :: !(Map (Path Abs Dir) Bool)}
instance HasBuildConfig EnvConfig where
getBuildConfig = envConfigBuildConfig
instance HasConfig EnvConfig
Expand Down
6 changes: 3 additions & 3 deletions src/main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -704,7 +704,7 @@ sdistCmd dirs go =
withBuildConfig go $ do -- No locking needed.
-- If no directories are specified, build all sdist tarballs.
dirs' <- if null dirs
then asks (Map.keys . bcPackages . getBuildConfig)
then asks (Map.keys . envConfigPackages . getEnvConfig)
else mapM (parseAbsDir <=< liftIO . canonicalizePath) dirs
forM_ dirs' $ \dir -> do
(tarName, tarBytes) <- getSDistTarball dir
Expand Down Expand Up @@ -762,9 +762,9 @@ ideCmd (targets,args) go@GlobalOpts{..} =
packagesCmd :: () -> GlobalOpts -> IO ()
packagesCmd () go@GlobalOpts{..} =
withBuildConfig go $
do bconfig <- asks getBuildConfig
do econfig <- asks getEnvConfig
locals <-
forM (M.toList (bcPackages bconfig)) $
forM (M.toList (envConfigPackages econfig)) $
\(dir,_) ->
do cabalfp <- getCabalFileName dir
parsePackageNameFromFilePath cabalfp
Expand Down

0 comments on commit 0f6a117

Please # to comment.