Skip to content

Commit

Permalink
Merge branch 'master' into task-prefix
Browse files Browse the repository at this point in the history
  • Loading branch information
mpilgrem authored Jan 13, 2024
2 parents 8ce1b19 + 8684038 commit b0f87cb
Show file tree
Hide file tree
Showing 19 changed files with 128 additions and 134 deletions.
12 changes: 6 additions & 6 deletions src/Stack/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,10 +97,10 @@ instance Exception CabalVersionPrettyException
-- | Helper for build and install commands
buildCmd :: BuildOptsCLI -> RIO Runner ()
buildCmd opts = do
when (any (("-prof" `elem`) . fromRight [] . parseArgs Escaping) opts.boptsCLIGhcOptions) $
when (any (("-prof" `elem`) . fromRight [] . parseArgs Escaping) opts.ghcOptions) $
prettyThrowIO GHCProfOptionInvalid
local (over globalOptsL modifyGO) $
case opts.boptsCLIFileWatch of
case opts.fileWatch of
FileWatchPoll -> fileWatchPoll (inner . Just)
FileWatch -> fileWatch (inner . Just)
NoFileWatch -> inner Nothing
Expand All @@ -112,7 +112,7 @@ buildCmd opts = do
Stack.Build.build setLocalFiles
-- Read the build command from the CLI and enable it to run
modifyGO =
case opts.boptsCLICommand of
case opts.command of
Test -> set
(globalOptsBuildOptsMonoidL . buildOptsMonoidTestsL)
(Just True)
Expand Down Expand Up @@ -150,7 +150,7 @@ build msetLocalFiles = do
stackYaml <- view stackYamlL
for_ msetLocalFiles $ \setLocalFiles -> do
files <-
if boptsCli.boptsCLIWatchAll
if boptsCli.watchAll
then sequence [lpFiles lp | lp <- allLocals]
else forM allLocals $ \lp -> do
let pn = lp.package.name
Expand All @@ -176,7 +176,7 @@ build msetLocalFiles = do
loadPackage
sourceMap
installedMap
boptsCli.boptsCLIInitialBuildSteps
boptsCli.initialBuildSteps

allowLocals <- view $ configL . to (.allowLocals)
unless allowLocals $ case justLocals plan of
Expand All @@ -190,7 +190,7 @@ build msetLocalFiles = do
when bopts.preFetch $
preFetch plan

if boptsCli.boptsCLIDryrun
if boptsCli.dryrun
then printPlan plan
else executePlan
boptsCli
Expand Down
28 changes: 14 additions & 14 deletions src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -225,7 +225,7 @@ constructPlan
toMaybe (k, Just v) = Just (k, v)

takeSubset :: Plan -> RIO env Plan
takeSubset = case baseConfigOpts0.bcoBuildOptsCLI.boptsCLIBuildSubset of
takeSubset = case baseConfigOpts0.bcoBuildOptsCLI.buildSubset of
BSAll -> pure
BSOnlySnapshot -> stripLocals
BSOnlyDependencies -> stripNonDeps
Expand Down Expand Up @@ -1016,16 +1016,16 @@ checkDirtiness ps installed package present buildHaddocks = do
(installLocationIsMutable $ psLocation ps) -- should be Local i.e. mutable always
package
wantConfigCache = ConfigCache
{ configCacheOpts = configOpts
, configCacheDeps = Set.fromList $ Map.elems present
, configCacheComponents =
{ opts = configOpts
, deps = Set.fromList $ Map.elems present
, components =
case ps of
PSFilePath lp ->
Set.map (encodeUtf8 . renderComponent) lp.components
PSRemote{} -> Set.empty
, configCacheHaddock = buildHaddocks
, configCachePkgSrc = toCachePkgSrc ps
, configCachePathEnvVar = ctx.pathEnvVar
, haddock = buildHaddocks
, pkgSrc = toCachePkgSrc ps
, pathEnvVar = ctx.pathEnvVar
}
config = view configL ctx
mreason <-
Expand All @@ -1051,16 +1051,16 @@ checkDirtiness ps installed package present buildHaddocks = do

describeConfigDiff :: Config -> ConfigCache -> ConfigCache -> Maybe Text
describeConfigDiff config old new
| old.configCachePkgSrc /= new.configCachePkgSrc = Just $
| old.pkgSrc /= new.pkgSrc = Just $
"switching from " <>
pkgSrcName old.configCachePkgSrc <> " to " <>
pkgSrcName new.configCachePkgSrc
| not (new.configCacheDeps `Set.isSubsetOf` old.configCacheDeps) =
pkgSrcName old.pkgSrc <> " to " <>
pkgSrcName new.pkgSrc
| not (new.deps `Set.isSubsetOf` old.deps) =
Just "dependencies changed"
| not $ Set.null newComponents =
Just $ "components added: " `T.append` T.intercalate ", "
(map (decodeUtf8With lenientDecode) (Set.toList newComponents))
| not old.configCacheHaddock && new.configCacheHaddock =
| not old.haddock && new.haddock =
Just "rebuilding with haddocks"
| oldOpts /= newOpts = Just $ T.pack $ concat
[ "flags changed from "
Expand Down Expand Up @@ -1098,7 +1098,7 @@ describeConfigDiff config old new
else stripGhcOptions)
. map T.pack
. (\(ConfigureOpts x y) -> x ++ y)
. (.configCacheOpts)
. (.opts)
where
-- options set by Stack
isStackOpt :: Text -> Bool
Expand Down Expand Up @@ -1132,7 +1132,7 @@ describeConfigDiff config old new
removeMatching xs ys = (xs, ys)

newComponents =
new.configCacheComponents `Set.difference` old.configCacheComponents
new.components `Set.difference` old.components

pkgSrcName (CacheSrcLocal fp) = T.pack fp
pkgSrcName CacheSrcUpstream = "upstream source"
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 @@ -330,7 +330,7 @@ executePlan
, esKeepGhcRts = False
}
withProcessContext menv' $
forM_ boptsCli.boptsCLIExec $ \(cmd, args) ->
forM_ boptsCli.exec $ \(cmd, args) ->
proc cmd args runProcess_
where
mlargestPackageName =
Expand Down Expand Up @@ -1126,7 +1126,7 @@ withSingleContext
AGOEverything
config.ghcOptionsByCat
++ case config.applyGhcOptions of
AGOEverything -> ee.buildOptsCLI.boptsCLIGhcOptions
AGOEverything -> ee.buildOptsCLI.ghcOptions
AGOTargets -> []
AGOLocals -> []
)
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/ExecuteEnv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -927,7 +927,7 @@ withSingleContext
AGOEverything
config.ghcOptionsByCat
++ case config.applyGhcOptions of
AGOEverything -> ee.buildOptsCLI.boptsCLIGhcOptions
AGOEverything -> ee.buildOptsCLI.ghcOptions
AGOTargets -> []
AGOLocals -> []
)
Expand Down
47 changes: 24 additions & 23 deletions src/Stack/Build/ExecutePackage.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}

-- | Perform a build
module Stack.Build.ExecutePackage
Expand Down Expand Up @@ -89,10 +90,11 @@ import Stack.Prelude
import Stack.Types.Build
( ConfigCache (..), PrecompiledCache (..)
, Task (..), TaskConfigOpts (..), TaskType (..)
, configCacheComponents, taskAnyMissing, taskIsTarget
, taskAnyMissing, taskIsTarget
, taskLocation, taskProvides
, taskTypePackageIdentifier
)
import qualified Stack.Types.Build as ConfigCache ( ConfigCache (..) )
import Stack.Types.Build.Exception
( BuildException (..), BuildPrettyException (..) )
import Stack.Types.BuildConfig
Expand Down Expand Up @@ -180,7 +182,7 @@ getConfigCache ee task installedMap enableTest enableBench = do
Nothing
-- Expect to instead find it in installedMap if it's
-- an initialBuildSteps target.
| ee.buildOptsCLI.boptsCLIInitialBuildSteps && taskIsTarget task
| ee.buildOptsCLI.initialBuildSteps && taskIsTarget task
, Just (_, installed) <- Map.lookup (pkgName ident) installedMap
-> pure $ installedToGhcPkgId ident installed
Just installed -> pure $ installedToGhcPkgId ident installed
Expand All @@ -194,18 +196,16 @@ getConfigCache ee task installedMap enableTest enableBench = do
opts = mkOpts missing'
allDeps = Set.fromList $ Map.elems missing' ++ Map.elems task.present
cache = ConfigCache
{ configCacheOpts = opts
{ coNoDirs = opts.coNoDirs ++ map T.unpack extra
}
, configCacheDeps = allDeps
, configCacheComponents =
{ opts = opts { coNoDirs = opts.coNoDirs ++ map T.unpack extra }
, deps = allDeps
, components =
case task.taskType of
TTLocalMutable lp ->
Set.map (encodeUtf8 . renderComponent) lp.components
TTRemotePackage{} -> Set.empty
, configCacheHaddock = task.buildHaddock
, configCachePkgSrc = task.cachePkgSrc
, configCachePathEnvVar = ee.pathEnvVar
, haddock = task.buildHaddock
, pkgSrc = task.cachePkgSrc
, pathEnvVar = ee.pathEnvVar
}
allDepsMap = Map.union missing' task.present
pure (allDepsMap, cache)
Expand Down Expand Up @@ -252,7 +252,8 @@ ensureConfig newConfigCache pkgDir buildOpts announce cabal cabalfp task = do
-- plan that we need to plan to build additional
-- components. These components don't affect the actual
-- package configuration.
let ignoreComponents cc = cc { configCacheComponents = Set.empty }
let ignoreComponents :: ConfigCache -> ConfigCache
ignoreComponents cc = cc { ConfigCache.components = Set.empty }
-- Determine the old and new configuration in the local directory, to
-- determine if we need to reconfigure.
mOldConfigCache <- tryGetConfigCache pkgDir
Expand All @@ -270,7 +271,7 @@ ensureConfig newConfigCache pkgDir buildOpts announce cabal cabalfp task = do
|| mOldCabalMod /= Just newCabalMod
|| mOldSetupConfigMod /= newSetupConfigMod
|| mOldProjectRoot /= Just newProjectRoot
let ConfigureOpts dirs nodirs = newConfigCache.configCacheOpts
let ConfigureOpts dirs nodirs = newConfigCache.opts

when task.buildTypeConfig $
-- When build-type is Configure, we need to have a configure script in the
Expand Down Expand Up @@ -438,8 +439,8 @@ singleBuild
TTRemotePackage Immutable _ loc -> do
mpc <- readPrecompiledCache
loc
cache.configCacheOpts
cache.configCacheHaddock
cache.opts
cache.haddock
case mpc of
Nothing -> pure Nothing
-- Only pay attention to precompiled caches that refer to packages
Expand Down Expand Up @@ -561,8 +562,8 @@ singleBuild
Just (_, Executable _) -> True
_ -> False

case ( ee.buildOptsCLI.boptsCLIOnlyConfigure
, ee.buildOptsCLI.boptsCLIInitialBuildSteps && taskIsTarget task
case ( ee.buildOptsCLI.onlyConfigure
, ee.buildOptsCLI.initialBuildSteps && taskIsTarget task
) of
-- A full build is done if there are downstream actions,
-- because their configure step will require that this
Expand Down Expand Up @@ -796,8 +797,8 @@ singleBuild
writePrecompiledCache
ee.baseConfigOpts
loc
cache.configCacheOpts
cache.configCacheHaddock
cache.opts
cache.haddock
mpkgid
subLibsPkgIds
(buildableExes package)
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/Haddock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ openHaddocksInBrowser ::
-- ^ Build targets as determined by 'Stack.Build.Source.loadSourceMap'
-> RIO env ()
openHaddocksInBrowser bco pkgLocations buildTargets = do
let cliTargets = bco.bcoBuildOptsCLI.boptsCLITargets
let cliTargets = bco.bcoBuildOptsCLI.targets
getDocIndex = do
let localDocs = haddockIndexFile (localDepsDocDir bco)
localExists <- doesFileExist localDocs
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,7 @@ loadSourceMap smt boptsCli sma = do
}
packageCliFlags = Map.fromList $
mapMaybe maybeProjectFlags $
Map.toList boptsCli.boptsCLIFlags
Map.toList boptsCli.flags
maybeProjectFlags (ACFByName name, fs) = Just (name, fs)
maybeProjectFlags _ = Nothing
globals = pruneGlobals sma.smaGlobal (Map.keysSet deps)
Expand Down Expand Up @@ -219,7 +219,7 @@ getLocalFlags boptsCli name = Map.unions
, Map.findWithDefault Map.empty ACFAllProjectPackages cliFlags
]
where
cliFlags = boptsCli.boptsCLIFlags
cliFlags = boptsCli.flags

-- | Get the options to pass to @./Setup.hs configure@
generalCabalConfigOpts ::
Expand Down Expand Up @@ -267,7 +267,7 @@ generalGhcOptions bconfig boptsCli isTarget isLocal = concat
else []
, [ "-g" | not $ bopts.libStrip || bopts.exeStrip ]
, if includeExtraOptions
then boptsCli.boptsCLIGhcOptions
then boptsCli.ghcOptions
else []
]
where
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 @@ -107,7 +107,7 @@ getRawInput ::
-> Map PackageName ProjectPackage
-> ([Text], [RawInput])
getRawInput boptscli locals =
let textTargets' = boptscli.boptsCLITargets
let textTargets' = boptscli.targets
textTargets =
-- Handle the no targets case, which means we pass in the names of all
-- project packages
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Coverage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,7 @@ hpcReportCmd hropts = do
let (tixFiles, targetNames) =
L.partition (".tix" `T.isSuffixOf`) hropts.hroptsInputs
boptsCLI = defaultBuildOptsCLI
{ boptsCLITargets = if hropts.hroptsAll then [] else targetNames }
{ targets = if hropts.hroptsAll then [] else targetNames }
withConfig YesReexec $ withEnvConfig AllowNoTargets boptsCLI $
generateHpcReportForTargets hropts tixFiles targetNames

Expand Down
4 changes: 2 additions & 2 deletions src/Stack/DependencyGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -163,8 +163,8 @@ withDotConfig opts inner =
runRIO dc inner

boptsCLI = defaultBuildOptsCLI
{ boptsCLITargets = opts.dotTargets
, boptsCLIFlags = opts.dotFlags
{ targets = opts.dotTargets
, flags = opts.dotFlags
}
modifyGO =
(if opts.dotTestTargets
Expand Down
4 changes: 1 addition & 3 deletions src/Stack/Exec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,9 +124,7 @@ execCmd opts =
eo = opts.eoExtra

targets = concatMap words eo.eoPackages
boptsCLI = defaultBuildOptsCLI
{ boptsCLITargets = map T.pack targets
}
boptsCLI = defaultBuildOptsCLI { targets = map T.pack targets }

-- return the package-id of the first package in GHC_PACKAGE_PATH
getPkgId name = do
Expand Down
16 changes: 8 additions & 8 deletions src/Stack/Ghci.hs
Original file line number Diff line number Diff line change
Expand Up @@ -201,10 +201,10 @@ ghciCmd :: GhciOpts -> RIO Runner ()
ghciCmd ghciOpts =
let boptsCLI = defaultBuildOptsCLI
-- using only additional packages, targets then get overridden in `ghci`
{ boptsCLITargets = map T.pack ghciOpts.ghciAdditionalPackages
, boptsCLIInitialBuildSteps = True
, boptsCLIFlags = ghciOpts.ghciFlags
, boptsCLIGhcOptions = map T.pack ghciOpts.ghciGhcOptions
{ targets = map T.pack ghciOpts.ghciAdditionalPackages
, initialBuildSteps = True
, flags = ghciOpts.ghciFlags
, ghcOptions = map T.pack ghciOpts.ghciGhcOptions
}
in withConfig YesReexec $ withEnvConfig AllowNoTargets boptsCLI $ do
bopts <- view buildOptsL
Expand All @@ -221,8 +221,8 @@ ghciCmd ghciOpts =
ghci :: HasEnvConfig env => GhciOpts -> RIO env ()
ghci opts = do
let buildOptsCLI = defaultBuildOptsCLI
{ boptsCLITargets = []
, boptsCLIFlags = opts.ghciFlags
{ targets = []
, flags = opts.ghciFlags
}
sourceMap <- view $ envConfigL . to (.sourceMap)
installMap <- toInstallMap sourceMap
Expand Down Expand Up @@ -320,7 +320,7 @@ preprocessTargets buildOptsCLI sma rawTargets = do
else do
-- Try parsing targets before checking if both file and
-- module targets are specified (see issue#3342).
let boptsCLI = buildOptsCLI { boptsCLITargets = normalTargetsRaw }
let boptsCLI = buildOptsCLI { targets = normalTargetsRaw }
normalTargets <- parseTargets AllowNoTargets False boptsCLI sma
`catch` \pex@(PrettyException ex) ->
case fromException $ toException ex of
Expand All @@ -337,7 +337,7 @@ parseMainIsTargets ::
-> Maybe Text
-> RIO env (Maybe (Map PackageName Target))
parseMainIsTargets buildOptsCLI sma mtarget = forM mtarget $ \target -> do
let boptsCLI = buildOptsCLI { boptsCLITargets = [target] }
let boptsCLI = buildOptsCLI { targets = [target] }
targets <- parseTargets AllowNoTargets False boptsCLI sma
pure targets.smtTargets

Expand Down
4 changes: 1 addition & 3 deletions src/Stack/Hoogle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -176,9 +176,7 @@ hoogleCmd (args, setup, rebuild, startServer) =
T.pack . packageIdentifierString <$>
restrictMinHoogleVersion muted hoogleIdent
config <- view configL
let boptsCLI = defaultBuildOptsCLI
{ boptsCLITargets = [hoogleTarget]
}
let boptsCLI = defaultBuildOptsCLI { targets = [hoogleTarget] }
runRIO config $ withEnvConfig NeedTargets boptsCLI f

restrictMinHoogleVersion ::
Expand Down
Loading

0 comments on commit b0f87cb

Please sign in to comment.