Skip to content

Commit

Permalink
Merge pull request #6456 from commercialhaskell/rename
Browse files Browse the repository at this point in the history
  • Loading branch information
mpilgrem authored Jan 21, 2024
2 parents 294b7d4 + cc4862d commit 4ad539e
Show file tree
Hide file tree
Showing 7 changed files with 42 additions and 37 deletions.
18 changes: 9 additions & 9 deletions src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,9 +155,9 @@ constructPlan
econfig <- view envConfigL
globalCabalVersion <- view $ compilerPathsL . to (.cabalVersion)
sources <- getSources globalCabalVersion
mcur <- view $ buildConfigL . to (.curator)
pathEnvVar' <- liftIO $ maybe mempty T.pack <$> lookupEnv "PATH"
let ctx = mkCtx econfig globalCabalVersion sources mcur pathEnvVar'
curator <- view $ buildConfigL . to (.curator)
pathEnvVar <- liftIO $ maybe mempty T.pack <$> lookupEnv "PATH"
let ctx = mkCtx econfig globalCabalVersion sources curator pathEnvVar
targetPackageNames = Map.keys sourceMap.targets.targets
-- Ignore the result of 'getCachedDepOrAddDep'.
onTarget = void . getCachedDepOrAddDep
Expand Down Expand Up @@ -204,17 +204,17 @@ constructPlan

hasBaseInDeps = Map.member (mkPackageName "base") sourceDeps

mkCtx econfig globalCabalVersion sources mcur pathEnvVar' = Ctx
mkCtx ctxEnvConfig globalCabalVersion sources curator pathEnvVar = Ctx
{ baseConfigOpts = baseConfigOpts0
, loadPackage = \w x y z -> runRIO econfig $
, loadPackage = \w x y z -> runRIO ctxEnvConfig $
applyForceCustomBuild globalCabalVersion <$> loadPackage0 w x y z
, combinedMap = combineMap sources installedMap
, ctxEnvConfig = econfig
, ctxEnvConfig
, callStack = []
, wanted = Map.keysSet sourceMap.targets.targets
, localNames = Map.keysSet sourceProject
, mcurator = mcur
, pathEnvVar = pathEnvVar'
, curator
, pathEnvVar
}

toEither :: (k, Either e v) -> Either e (k, v)
Expand Down Expand Up @@ -662,7 +662,7 @@ installPackage name ps minstalled = do
-- test/benchmark failure could prevent library from being
-- available to its dependencies but when it's already available
-- it's OK to do that
splitRequired <- expectedTestOrBenchFailures <$> asks (.mcurator)
splitRequired <- expectedTestOrBenchFailures <$> asks (.curator)
let isAllInOne = not splitRequired
adr <- installPackageGivenDeps
isAllInOne lp.buildHaddocks ps tb minstalled deps
Expand Down
8 changes: 4 additions & 4 deletions src/Stack/Build/ExecutePackage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -369,8 +369,8 @@ singleBuild
case mprecompiled of
Just precompiled -> copyPreCompiled ee task pkgId precompiled
Nothing -> do
mcurator <- view $ buildConfigL . to (.curator)
realConfigAndBuild cache mcurator allDepsMap
curator <- view $ buildConfigL . to (.curator)
realConfigAndBuild cache curator allDepsMap
case minstalled of
Nothing -> pure ()
Just installed -> do
Expand All @@ -380,15 +380,15 @@ singleBuild
where
pkgId = taskProvides task
PackageIdentifier pname _ = pkgId
doHaddock mcurator package =
doHaddock curator package =
task.buildHaddock
&& not isFinalBuild
-- Works around haddock failing on bytestring-builder since it has no
-- modules when bytestring is new enough.
&& mainLibraryHasExposedModules package
-- Special help for the curator tool to avoid haddocks that are known
-- to fail
&& maybe True (Set.notMember pname . (.skipHaddock)) mcurator
&& maybe True (Set.notMember pname . (.skipHaddock)) curator

buildingFinals = isFinalBuild || task.allInOne
enableTests = buildingFinals && any isCTest (taskComponents task)
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -833,7 +833,7 @@ withBuildConfig inner = do
pure Project
{ userMsg = Nothing
, packages = []
, dependencies = map (RPLImmutable . flip RPLIHackage Nothing) extraDeps
, extraDeps = map (RPLImmutable . flip RPLIHackage Nothing) extraDeps
, flagsByPkg = mempty
, resolver = r
, compiler = Nothing
Expand Down Expand Up @@ -867,11 +867,11 @@ fillProjectWanted stackYamlFP config project locCache snapCompiler snapPackages
(RPLImmutable (RPLIRepo repo rpm)) -> Just (repo, rpm)
_ -> Nothing
)
project.dependencies
project.extraDeps
logDebug ("Prefetching git repos: " <> display (T.pack (show gitRepos)))
fetchReposRaw gitRepos

(deps0, mcompleted) <- fmap unzip . forM project.dependencies $ \rpl -> do
(deps0, mcompleted) <- fmap unzip . forM project.extraDeps $ \rpl -> do
(pl, mCompleted) <- case rpl of
RPLImmutable rpli -> do
(compl, mcompl) <-
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Init.hs
Original file line number Diff line number Diff line change
Expand Up @@ -281,10 +281,10 @@ initProject currDir initOpts mresolver = do
PLImmutable . cplComplete <$>
completePackageLocation
(RPLIHackage (PackageIdentifierRevision n v CFILatest) Nothing)
let p = Project
let project = Project
{ userMsg = if userMsg == "" then Nothing else Just userMsg
, packages = resolvedRelative <$> Map.elems rbundle
, dependencies = map toRawPL deps
, extraDeps = map toRawPL deps
, flagsByPkg = removeSrcPkgDefaultFlags gpds flags
, resolver = snapshotLoc
, compiler = Nothing
Expand Down Expand Up @@ -336,7 +336,7 @@ initProject currDir initOpts mresolver = do
else "Writing configuration to"
, style File (fromString reldest) <> "."
]
writeBinaryFileAtomic dest $ renderStackYaml p
writeBinaryFileAtomic dest $ renderStackYaml project
(Map.elems $ fmap (makeRelDir . parent . fst) ignored)
(map (makeRelDir . parent) dupPkgs)
prettyInfoS
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Types/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -161,7 +161,7 @@ data Ctx = Ctx
, callStack :: ![PackageName]
, wanted :: !(Set PackageName)
, localNames :: !(Set PackageName)
, mcurator :: !(Maybe Curator)
, curator :: !(Maybe Curator)
, pathEnvVar :: !Text
}

Expand Down
35 changes: 20 additions & 15 deletions src/Stack/Types/Project.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NoFieldSelectors #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NoFieldSelectors #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}

module Stack.Types.Project
( Project (..)
Expand All @@ -21,7 +22,7 @@ data Project = Project
, packages :: ![RelFilePath]
-- ^ Packages which are actually part of the project (as opposed
-- to dependencies).
, dependencies :: ![RawPackageLocation]
, extraDeps :: ![RawPackageLocation]
-- ^ Dependencies defined within the stack.yaml file, to be applied on top
-- of the snapshot.
, flagsByPkg :: !(Map PackageName (Map FlagName Bool))
Expand All @@ -42,16 +43,20 @@ data Project = Project

instance ToJSON Project where
-- Expanding the constructor fully to ensure we don't miss any fields.
toJSON (Project userMsg packages extraDeps flags resolver mcompiler extraPackageDBs mcurator drops) = object $ concat
[ maybe [] (\cv -> ["compiler" .= cv]) mcompiler
, maybe [] (\msg -> ["user-message" .= msg]) userMsg
, [ "extra-package-dbs" .= extraPackageDBs | not (null extraPackageDBs) ]
, [ "extra-deps" .= extraDeps | not (null extraDeps) ]
, [ "flags" .= fmap toCabalStringMap (toCabalStringMap flags)
| not (Map.null flags)
toJSON project = object $ concat
[ maybe [] (\cv -> ["compiler" .= cv]) project.compiler
, maybe [] (\msg -> ["user-message" .= msg]) project.userMsg
, [ "extra-package-dbs" .= project.extraPackageDBs
| not (null project.extraPackageDBs)
]
, [ "extra-deps" .= project.extraDeps | not (null project.extraDeps) ]
, [ "flags" .= fmap toCabalStringMap (toCabalStringMap project.flagsByPkg)
| not (Map.null project.flagsByPkg)
]
, ["packages" .= project.packages]
, ["resolver" .= project.resolver]
, maybe [] (\c -> ["curator" .= c]) project.curator
, [ "drop-packages" .= Set.map CabalString project.dropPackages
| not (Set.null project.dropPackages)
]
, ["packages" .= packages]
, ["resolver" .= resolver]
, maybe [] (\c -> ["curator" .= c]) mcurator
, [ "drop-packages" .= Set.map CabalString drops | not (Set.null drops) ]
]
4 changes: 2 additions & 2 deletions src/Stack/Types/ProjectAndConfigMonoid.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ parseProjectAndConfigMonoid rootDir =
let dropPackages = Set.map unCabalString drops
pure $ do
deps' <- mapM (resolvePaths (Just rootDir)) deps
let dependencies =
let extraDeps =
concatMap toList (deps' :: [NonEmpty RawPackageLocation])
resolver <- resolvePaths (Just rootDir) resolver'
let project = Project
Expand All @@ -52,7 +52,7 @@ parseProjectAndConfigMonoid rootDir =
, compiler -- FIXME make sure resolver' isn't SLCompiler
, extraPackageDBs
, packages
, dependencies
, extraDeps
, flagsByPkg
, curator
, dropPackages
Expand Down

0 comments on commit 4ad539e

Please sign in to comment.