Skip to content

Commit

Permalink
Various renaming for consistency
Browse files Browse the repository at this point in the history
  • Loading branch information
mpilgrem committed Jan 22, 2024
1 parent 4306bf7 commit 5329601
Show file tree
Hide file tree
Showing 26 changed files with 136 additions and 134 deletions.
12 changes: 6 additions & 6 deletions src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -447,11 +447,11 @@ addFinal lp package isAllInOne buildHaddocks = do
True -- local
Mutable
package
, buildHaddock = buildHaddocks
, present = present
, buildHaddocks
, present
, taskType = TTLocalMutable lp
, allInOne = isAllInOne
, cachePkgSrc = CacheSrcLocal (toFilePath (parent lp.cabalFile))
, cachePkgSrc = CacheSrcLocal (toFilePath (parent lp.cabalFP))
, buildTypeConfig = packageBuildTypeConfig package
}
tell mempty { wFinals = Map.singleton package.name res }
Expand Down Expand Up @@ -632,7 +632,7 @@ installPackage name ps minstalled = do
<> "."
package <- ctx.loadPackage
pkgLoc cp.flags cp.ghcOptions cp.cabalConfigOpts
resolveDepsAndInstall True cp.haddocks ps package minstalled
resolveDepsAndInstall True cp.buildHaddocks ps package minstalled
PSFilePath lp -> do
case lp.testBench of
Nothing -> do
Expand Down Expand Up @@ -760,8 +760,8 @@ installPackageGivenDeps isAllInOne buildHaddocks ps package minstalled
(psLocal ps)
mutable
package
, buildHaddock = buildHaddocks
, present = present
, buildHaddocks
, present
, taskType =
case ps of
PSFilePath lp ->
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Build/Execute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,7 +186,7 @@ displayTask task = fillSep $
<> ","
, "source="
<> ( case task.taskType of
TTLocalMutable lp -> pretty $ parent lp.cabalFile
TTLocalMutable lp -> pretty $ parent lp.cabalFP
TTRemotePackage _ _ pl -> fromString $ T.unpack $ textDisplay pl
)
<> if Set.null missing
Expand Down Expand Up @@ -419,7 +419,7 @@ executePlan' installedMap0 targets plan ee = do
generateHpcMarkupIndex
unless (null errs) $
prettyThrowM $ ExecutionFailure errs
when buildOpts.haddock $ do
when buildOpts.buildHaddocks $ do
if buildOpts.haddockForHackage
then
generateLocalHaddockForHackageArchives ee.locals
Expand Down
12 changes: 6 additions & 6 deletions src/Stack/Build/ExecuteEnv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -577,10 +577,10 @@ withSingleContext
allDeps
msuffix
inner0
= withPackage $ \package cabalfp pkgDir ->
= withPackage $ \package cabalFP pkgDir ->
withOutputType pkgDir package $ \outputType ->
withCabal package pkgDir outputType $ \cabal ->
inner0 package cabalfp pkgDir cabal announce outputType
inner0 package cabalFP pkgDir cabal announce outputType
where
pkgId = taskTypePackageIdentifier taskType
announce = announceTask ee taskType
Expand Down Expand Up @@ -610,9 +610,9 @@ withSingleContext
withPackage inner =
case taskType of
TTLocalMutable lp -> do
let root = parent lp.cabalFile
let root = parent lp.cabalFP
withLockedDistDir prettyAnnounce root $
inner lp.package lp.cabalFile root
inner lp.package lp.cabalFP root
TTRemotePackage _ package pkgloc -> do
suffix <-
parseRelDir $ packageIdentifierString $ packageIdentifier package
Expand All @@ -635,8 +635,8 @@ withSingleContext

let name = pkgName pkgId
cabalfpRel <- parseRelFile $ packageNameString name ++ ".cabal"
let cabalfp = dir </> cabalfpRel
inner package cabalfp dir
let cabalFP = dir </> cabalfpRel
inner package cabalFP dir

withOutputType pkgDir package inner
-- Not in interleaved mode. When building a single wanted package, dump
Expand Down
20 changes: 10 additions & 10 deletions src/Stack/Build/ExecutePackage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -196,7 +196,7 @@ getConfigCache ee task installedMap enableTest enableBench = do
TTLocalMutable lp ->
Set.map (encodeUtf8 . renderComponent) lp.components
TTRemotePackage{} -> Set.empty
, haddock = task.buildHaddock
, haddock = task.buildHaddocks
, pkgSrc = task.cachePkgSrc
, pathEnvVar = ee.pathEnvVar
}
Expand All @@ -213,9 +213,9 @@ ensureConfig :: HasEnvConfig env
-> Path Abs File -- ^ Cabal file
-> Task
-> RIO env Bool
ensureConfig newConfigCache pkgDir buildOpts announce cabal cabalfp task = do
ensureConfig newConfigCache pkgDir buildOpts announce cabal cabalFP task = do
newCabalMod <-
liftIO $ modificationTime <$> getFileStatus (toFilePath cabalfp)
liftIO $ modificationTime <$> getFileStatus (toFilePath cabalFP)
setupConfigfp <- setupConfigFromDir pkgDir
let getNewSetupConfigMod =
liftIO $ either (const Nothing) (Just . modificationTime) <$>
Expand Down Expand Up @@ -381,7 +381,7 @@ singleBuild
pkgId = taskProvides task
PackageIdentifier pname _ = pkgId
doHaddock curator package =
task.buildHaddock
task.buildHaddocks
&& not isFinalBuild
-- Works around haddock failing on bytestring-builder since it has no
-- modules when bytestring is new enough.
Expand Down Expand Up @@ -417,7 +417,7 @@ singleBuild

realConfigAndBuild cache mcurator allDepsMap =
withSingleContext ac ee task.taskType allDepsMap Nothing $
\package cabalfp pkgDir cabal0 announce _outputType -> do
\package cabalFP pkgDir cabal0 announce _outputType -> do
let cabal = cabal0 CloseOnException
executableBuildStatuses <- getExecutableBuildStatuses package pkgDir
when ( not (cabalIsSatisfied executableBuildStatuses)
Expand All @@ -440,7 +440,7 @@ singleBuild
)
)
cabal
cabalfp
cabalFP
task
let installedMapHasThisPkg :: Bool
installedMapHasThisPkg =
Expand Down Expand Up @@ -506,7 +506,7 @@ singleBuild
TTLocalMutable lp -> do
warnings <- checkForUnlistedFiles task.taskType pkgDir
-- TODO: Perhaps only emit these warnings for non extra-dep?
pure (Just (lp.cabalFile, warnings))
pure (Just (lp.cabalFP, warnings))
_ -> pure Nothing
-- NOTE: once
-- https://github.com/commercialhaskell/stack/issues/2649
Expand All @@ -522,11 +522,11 @@ singleBuild
(style Good . fromString . C.display)
modules
)
forM_ mlocalWarnings $ \(cabalfp, warnings) ->
forM_ mlocalWarnings $ \(cabalFP, warnings) ->
unless (null warnings) $ prettyWarn $
flow "The following modules should be added to \
\exposed-modules or other-modules in" <+>
pretty cabalfp
pretty cabalFP
<> ":"
<> line
<> indent 4 ( mconcat
Expand Down Expand Up @@ -904,7 +904,7 @@ checkForUnlistedFiles (TTLocalMutable lp) pkgDir = do
(addBuildCache,warnings) <-
addUnlistedToBuildCache
lp.package
lp.cabalFile
lp.cabalFP
lp.components
caches
forM_ (Map.toList addBuildCache) $ \(component, newToCache) -> do
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Build/Haddock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,12 +110,12 @@ shouldHaddockPackage ::
-> Bool
shouldHaddockPackage bopts wanted name =
if Set.member name wanted
then bopts.haddock
then bopts.buildHaddocks
else shouldHaddockDeps bopts

-- | Determine whether to build haddocks for dependencies.
shouldHaddockDeps :: BuildOpts -> Bool
shouldHaddockDeps bopts = fromMaybe bopts.haddock bopts.haddockDeps
shouldHaddockDeps bopts = fromMaybe bopts.buildHaddocks bopts.haddockDeps

-- | Generate Haddock index and contents for local packages.
generateLocalHaddockIndex ::
Expand Down Expand Up @@ -341,7 +341,7 @@ generateLocalHaddockForHackageArchives =
( \lp ->
let pkg = lp.package
pkgId = PackageIdentifier pkg.name pkg.version
pkgDir = parent lp.cabalFile
pkgDir = parent lp.cabalFP
in generateLocalHaddockForHackageArchive pkgDir pkgId
)

Expand Down
12 changes: 6 additions & 6 deletions src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -125,17 +125,17 @@ loadSourceMap targets boptsCli sma = do
ghcOptions ++ common.ghcOptions
, cabalConfigOpts =
cabalConfigOpts ++ common.cabalConfigOpts
, haddocks =
, buildHaddocks =
if isTarget
then bopts.haddock
then bopts.buildHaddocks
else shouldHaddockDeps bopts
}
packageCliFlags = Map.fromList $
mapMaybe maybeProjectFlags $
Map.toList boptsCli.flags
maybeProjectFlags (ACFByName name, fs) = Just (name, fs)
maybeProjectFlags _ = Nothing
globalPkgs = pruneGlobals sma.global (Map.keysSet deps)
globalPkgs = pruneGlobals sma.globals (Map.keysSet deps)
logDebug "Checking flags"
checkFlagsUsedThrowing packageCliFlags FSCommandLine project deps
logDebug "SourceMap constructed"
Expand Down Expand Up @@ -200,7 +200,7 @@ depPackageHashableContent dp =
flags = map flagToBs $ Map.toList dp.depCommon.flags
ghcOptions = map display dp.depCommon.ghcOptions
cabalConfigOpts = map display dp.depCommon.cabalConfigOpts
haddocks = if dp.depCommon.haddocks then "haddocks" else ""
haddocks = if dp.depCommon.buildHaddocks then "haddocks" else ""
hash = immutableLocSha pli
pure
$ hash
Expand Down Expand Up @@ -409,11 +409,11 @@ loadLocalPackage pp = do
{ package = pkg
, testBench = btpkg
, componentFiles
, buildHaddocks = pp.projectCommon.haddocks
, buildHaddocks = pp.projectCommon.buildHaddocks
, forceDirty = bopts.forceDirty
, dirtyFiles
, newBuildCaches
, cabalFile = pp.cabalFP
, cabalFP = pp.cabalFP
, wanted = isWanted
, components = nonLibComponents
-- TODO: refactor this so that it's easier to be sure that these
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/Target.hs
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@ resolveRawTarget sma allLocs (rawInput, rt) =
where
locals = sma.project
deps = sma.deps
globals = sma.global
globals = sma.globals
-- Helper function: check if a 'NamedComponent' matches the given
-- 'ComponentName'
isCompNamed :: ComponentName -> NamedComponent -> Bool
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/BuildOpts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ defaultBuildOpts = BuildOpts
, exeProfile = defaultFirstFalse buildMonoid.exeProfile
, libStrip = defaultFirstTrue buildMonoid.libStrip
, exeStrip = defaultFirstTrue buildMonoid.exeStrip
, haddock = False
, buildHaddocks = False
, haddockOpts = defaultHaddockOpts
, openHaddocks = defaultFirstFalse buildMonoid.openHaddocks
, haddockDeps = Nothing
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/BuildPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -390,7 +390,7 @@ checkSnapBuildPlan pkgDirs flags snapCandidate = do
| otherwise = Nothing
snapPkgs = Map.union
(Map.mapMaybe depVersion sma.deps)
(Map.map globalVersion sma.global)
(Map.map globalVersion sma.globals)
(f, errs) = checkBundleBuildPlan platform compiler snapPkgs flags gpds
cerrs = compilerErrors compiler errs

Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -857,7 +857,7 @@ fillProjectWanted stackYamlFP config project locCache snapCompiler snapPackages
packages0 <- for project.packages $ \fp@(RelFilePath t) -> do
abs' <- resolveDir (parent stackYamlFP) (T.unpack t)
let resolved = ResolvedPath fp abs'
pp <- mkProjectPackage YesPrintWarnings resolved bopts.haddock
pp <- mkProjectPackage YesPrintWarnings resolved bopts.buildHaddocks
pure (pp.projectCommon.name, pp)

-- prefetch git repos to avoid cloning per subdirectory
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Config/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ buildOptsFromMonoid buildMonoid = BuildOpts
( buildMonoid.exeStrip
<> FirstTrue (if noStripping then Just False else Nothing)
)
, haddock = fromFirstFalse buildMonoid.haddock
, buildHaddocks = fromFirstFalse buildMonoid.buildHaddocks
, haddockOpts = haddockOptsFromMonoid buildMonoid.haddockOpts
, openHaddocks =
not isHaddockFromHackage
Expand Down
8 changes: 4 additions & 4 deletions src/Stack/DependencyGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ withDotConfig opts inner =
{ compiler = actual
, project = buildConfig.smWanted.project
, deps = buildConfig.smWanted.deps
, global = Map.mapWithKey toDump globals
, globals = Map.mapWithKey toDump globals
}
toDump :: PackageName -> Version -> DumpPackage
toDump name version = DumpPackage
Expand All @@ -136,14 +136,14 @@ withDotConfig opts inner =
actualPkgs =
Map.keysSet smActual.deps <> Map.keysSet smActual.project
prunedActual = smActual
{ global = pruneGlobals smActual.global actualPkgs }
{ globals = pruneGlobals smActual.globals actualPkgs }
targets <- parseTargets NeedTargets False boptsCLI prunedActual
logDebug "Loading source map"
sourceMap <- loadSourceMap targets boptsCLI smActual
let dc = DotConfig
{ buildConfig
, sourceMap
, globalDump = toList smActual.global
, globalDump = toList smActual.globals
}
logDebug "DotConfig fully loaded"
runRIO dc inner
Expand Down Expand Up @@ -216,7 +216,7 @@ projectPackageDependencies ::
-> [(PackageName, (Set PackageName, DotPayload))]
projectPackageDependencies dotOpts locals =
map (\lp -> let pkg = localPackageToPackage lp
pkgDir = parent lp.cabalFile
pkgDir = parent lp.cabalFP
packageDepsSet = setOfPackageDeps pkg
loc = PLMutable $ ResolvedPath (RelFilePath "N/A") pkgDir
in (pkg.name, (deps pkg packageDepsSet, lpPayload pkg loc)))
Expand Down
26 changes: 13 additions & 13 deletions src/Stack/Ghci.hs
Original file line number Diff line number Diff line change
Expand Up @@ -238,7 +238,7 @@ ghci opts = do
{ compiler = sourceMap.compiler
, project = sourceMap.project
, deps = sourceMap.deps
, global = sourceMap.globalPkgs
, globals = sourceMap.globalPkgs
}
-- Parse --main-is argument.
mainIsTargets <- parseMainIsTargets buildOptsCLI sma opts.mainIs
Expand Down Expand Up @@ -356,7 +356,7 @@ findFileTargets ::
-> RIO env (Map PackageName Target, Map PackageName [Path Abs File], [Path Abs File])
findFileTargets locals fileTargets = do
filePackages <- forM locals $ \lp -> do
PackageComponentFile _ compFiles _ _ <- getPackageFile lp.package lp.cabalFile
PackageComponentFile _ compFiles _ _ <- getPackageFile lp.package lp.cabalFP
pure (lp, M.map (map dotCabalGetPath) compFiles)
let foundFileTargetComponents :: [(Path Abs File, [(PackageName, NamedComponent)])]
foundFileTargetComponents =
Expand Down Expand Up @@ -831,8 +831,8 @@ loadGhciPkgDescs ::
-> [(PackageName, (Path Abs File, Target))]
-> RIO env [GhciPkgDesc]
loadGhciPkgDescs buildOptsCLI localTargets =
forM localTargets $ \(name, (cabalfp, target)) ->
loadGhciPkgDesc buildOptsCLI name cabalfp target
forM localTargets $ \(name, (cabalFP, target)) ->
loadGhciPkgDesc buildOptsCLI name cabalFP target

-- | Load package description information for a ghci target.
loadGhciPkgDesc ::
Expand Down Expand Up @@ -868,11 +868,11 @@ loadGhciPkgDesc buildOptsCLI name cabalFP target = do
, compilerVersion = compilerVersion
, platform = view platformL econfig
}
-- TODO we've already parsed this information, otherwise we
-- wouldn't have figured out the cabalfp already. In the future:
-- retain that GenericPackageDescription in the relevant data
-- structures to avoid reparsing.
(gpdio, _name, _cabalfp) <-
-- TODO we've already parsed this information, otherwise we wouldn't have
-- figured out the cabalFP already. In the future: retain that
-- GenericPackageDescription in the relevant data structures to avoid
-- reparsing.
(gpdio, _name, _cabalFP) <-
loadCabalFilePath (Just stackProgName') (parent cabalFP)
gpkgdesc <- liftIO $ gpdio YesPrintWarnings

Expand Down Expand Up @@ -924,18 +924,18 @@ makeGhciPkgInfo ::
makeGhciPkgInfo installMap installedMap locals addPkgs mfileTargets pkgDesc = do
bopts <- view buildOptsL
let pkg = pkgDesc.package
cabalfp = pkgDesc.cabalFP
cabalFP = pkgDesc.cabalFP
target = pkgDesc.target
name = pkg.name
(mods, files, opts) <-
getPackageOpts pkg installMap installedMap locals addPkgs cabalfp
getPackageOpts pkg installMap installedMap locals addPkgs cabalFP
let filteredOpts = filterWanted opts
filterWanted = M.filterWithKey (\k _ -> k `S.member` allWanted)
allWanted = wantedPackageComponents bopts target pkg
pure GhciPkgInfo
{ name
, opts = M.toList filteredOpts
, dir = parent cabalfp
, dir = parent cabalFP
, modules = unionModuleMaps $
map
( \(comp, mp) -> M.map
Expand Down Expand Up @@ -1211,7 +1211,7 @@ getExtraLoadDeps loadAllDeps localMap targets =
shouldLoad <- or <$> mapM go deps
if shouldLoad
then do
modify (M.insert name (Just (lp.cabalFile, TargetComps (S.singleton CLib))))
modify (M.insert name (Just (lp.cabalFP, TargetComps (S.singleton CLib))))
pure True
else do
modify (M.insert name Nothing)
Expand Down
Loading

0 comments on commit 5329601

Please sign in to comment.