Skip to content

Commit

Permalink
Remove config prefix from Config field names
Browse files Browse the repository at this point in the history
  • Loading branch information
mpilgrem committed Jan 13, 2024
1 parent a492ce5 commit 583275c
Show file tree
Hide file tree
Showing 33 changed files with 385 additions and 380 deletions.
4 changes: 2 additions & 2 deletions src/Stack/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,7 @@ build :: HasEnvConfig env
=> Maybe (Set (Path Abs File) -> IO ()) -- ^ callback after discovering all local files
-> RIO env ()
build msetLocalFiles = do
mcp <- view $ configL . to (.configModifyCodePage)
mcp <- view $ configL . to (.modifyCodePage)
ghcVersion <- view $ actualCompilerVersionL . to getGhcVersion
fixCodePage mcp ghcVersion $ do
bopts <- view buildOptsL
Expand Down Expand Up @@ -178,7 +178,7 @@ build msetLocalFiles = do
installedMap
boptsCli.boptsCLIInitialBuildSteps

allowLocals <- view $ configL . to (.configAllowLocals)
allowLocals <- view $ configL . to (.allowLocals)
unless allowLocals $ case justLocals plan of
[] -> pure ()
localsIdents -> throwM $ LocalPackagesPresent localsIdents
Expand Down
12 changes: 6 additions & 6 deletions src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,7 +188,7 @@ constructPlan
stackYaml <- view stackYamlL
stackRoot <- view stackRootL
isImplicitGlobal <-
view $ configL . to (isPCGlobalProject . (.configProject))
view $ configL . to (isPCGlobalProject . (.project))
prettyThrowM $ ConstructPlanFailed
errs
stackYaml
Expand Down Expand Up @@ -297,7 +297,7 @@ constructPlan
pPackages <- for sourceProject $ \pp -> do
lp <- loadLocalPackage' pp
pure $ PSFilePath lp
bopts <- view $ configL . to (.configBuild)
bopts <- view $ configL . to (.build)
deps <- for sourceDeps $ \dp ->
case dp.dpLocation of
PLImmutable loc ->
Expand Down Expand Up @@ -901,8 +901,8 @@ adrInRange ::
adrInRange pkgId name range adr = if adrVersion adr `withinRange` range
then pure True
else do
allowNewer <- view $ configL . to (.configAllowNewer)
allowNewerDeps <- view $ configL . to (.configAllowNewerDeps)
allowNewer <- view $ configL . to (.allowNewer)
allowNewerDeps <- view $ configL . to (.allowNewerDeps)
if allowNewer
then case allowNewerDeps of
Nothing -> do
Expand Down Expand Up @@ -1093,7 +1093,7 @@ describeConfigDiff config old new
isKeeper = (== "-fhpc") -- more to be added later

userOpts = filter (not . isStackOpt)
. (if config.configRebuildGhcOptions
. (if config.rebuildGhcOptions
then id
else stripGhcOptions)
. map T.pack
Expand Down Expand Up @@ -1174,7 +1174,7 @@ checkAndWarnForUnknownTools p = do
notOnPath toolName = MaybeT $ do
let settings = minimalEnvSettings { esIncludeLocals = True }
config <- view configL
menv <- liftIO $ config.configProcessContextSettings settings
menv <- liftIO $ config.processContextSettings settings
eFound <- runRIO menv $ findExecutable $ T.unpack toolName
skipIf $ isRight eFound
-- From Cabal 1.12, build-tools can specify another executable in the same
Expand Down
28 changes: 14 additions & 14 deletions src/Stack/Build/Execute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -562,7 +562,7 @@ withExecuteEnv bopts boptsCli baseConfigOpts locals globalPackages snapshotPacka
-- No log files generated, nothing to dump
[] -> pure ()
firstLog:_ -> do
toDump <- view $ configL . to (.configDumpLogs)
toDump <- view $ configL . to (.dumpLogs)
case toDump of
DumpAllLogs -> mapM_ (dumpLog "") allLogs
DumpWarningLogs -> mapM_ dumpLogIfWarning allLogs
Expand Down Expand Up @@ -698,7 +698,7 @@ executePlan
copyExecutables plan.planInstallExes

config <- view configL
menv' <- liftIO $ config.configProcessContextSettings EnvSettings
menv' <- liftIO $ config.processContextSettings EnvSettings
{ esIncludeLocals = True
, esIncludeGhcPackagePath = True
, esStackExe = True
Expand All @@ -725,7 +725,7 @@ copyExecutables exes = do
compilerSpecific <- (.boptsInstallCompilerTool) <$> view buildOptsL
destDir <- if compilerSpecific
then bindirCompilerTools
else view $ configL . to (.configLocalBin)
else view $ configL . to (.localBin)
ensureDir destDir

destDir' <- liftIO . D.canonicalizePath . toFilePath $ destDir
Expand Down Expand Up @@ -815,7 +815,7 @@ executePlan' installedMap0 targets plan ee = do

-- If running tests concurrently with each other, then create an MVar
-- which is empty while each test is being run.
concurrentTests <- view $ configL . to (.configConcurrentTests)
concurrentTests <- view $ configL . to (.concurrentTests)
mtestLock <- if concurrentTests
then pure Nothing
else Just <$> liftIO (newMVar ())
Expand All @@ -827,7 +827,7 @@ executePlan' installedMap0 targets plan ee = do
(Map.zipWithMatched (\_ b f -> (Just b, Just f)))
plan.planTasks
plan.planFinals
threads <- view $ configL . to (.configJobs)
threads <- view $ configL . to (.jobs)
let keepGoing = fromMaybe
(not (Map.null plan.planFinals))
ee.eeBuildOpts.boptsKeepGoing
Expand Down Expand Up @@ -1428,16 +1428,16 @@ withSingleContext
-> RIO env a
withCabal package pkgDir outputType inner = do
config <- view configL
unless config.configAllowDifferentUser $
checkOwnership (pkgDir </> config.configWorkDir)
unless config.allowDifferentUser $
checkOwnership (pkgDir </> config.workDir)
let envSettings = EnvSettings
{ esIncludeLocals = taskTypeLocation taskType == Local
, esIncludeGhcPackagePath = False
, esStackExe = False
, esLocaleUtf8 = True
, esKeepGhcRts = False
}
menv <- liftIO $ config.configProcessContextSettings envSettings
menv <- liftIO $ config.processContextSettings envSettings
distRelativeDir' <- distRelativeDir
esetupexehs <-
-- Avoid broken Setup.hs files causing problems for simple build
Expand Down Expand Up @@ -1601,7 +1601,7 @@ withSingleContext
withProcessContext menv $ case outputType of
OTLogFile _ h -> do
let prefixWithTimestamps =
if config.configPrefixTimestamps
if config.prefixTimestamps
then PrefixWithTimestamps
else WithoutTimestamps
void $ sinkProcessStderrStdout (toFilePath exeName) fullArgs
Expand Down Expand Up @@ -1665,8 +1665,8 @@ withSingleContext
( Map.findWithDefault
[]
AGOEverything
config.configGhcOptionsByCat
++ case config.configApplyGhcOptions of
config.ghcOptionsByCat
++ case config.applyGhcOptions of
AGOEverything -> ee.eeBuildOptsCLI.boptsCLIGhcOptions
AGOTargets -> []
AGOLocals -> []
Expand Down Expand Up @@ -2004,7 +2004,7 @@ singleBuild
config <- view configL
extraOpts <- extraBuildOptions wc ee.eeBuildOpts
let stripTHLoading
| config.configHideTHLoading = ExcludeTHLoading
| config.hideTHLoading = ExcludeTHLoading
| otherwise = KeepTHLoading
cabal stripTHLoading (("build" :) $ (++ extraOpts) $
case (task.taskType, task.taskAllInOne, isFinalBuild) of
Expand Down Expand Up @@ -2310,7 +2310,7 @@ singleTest topts testsToRun ac ee task installedMap = do
interface -> throwM (TestSuiteTypeUnsupported interface)

let exeName = testName' ++
case config.configPlatform of
case config.platform of
Platform _ Windows -> ".exe"
_ -> ""
tixPath <- fmap (pkgDir </>) $ parseRelFile $ exeName ++ ".tix"
Expand Down Expand Up @@ -2372,7 +2372,7 @@ singleTest topts testsToRun ac ee task installedMap = do
(pkgGhcIdList ++ thGhcId:Map.elems allDepsMap)
writeFileUtf8Builder fp ghcEnv
menv <- liftIO $
setEnv fp =<< config.configProcessContextSettings EnvSettings
setEnv fp =<< config.processContextSettings EnvSettings
{ esIncludeLocals = taskLocation task == Local
, esIncludeGhcPackagePath = True
, esStackExe = True
Expand Down
24 changes: 12 additions & 12 deletions src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ projectLocalPackages = do
-- | loads all local dependencies - project packages and local extra-deps
localDependencies :: HasEnvConfig env => RIO env [LocalPackage]
localDependencies = do
bopts <- view $ configL . to (.configBuild)
bopts <- view $ configL . to (.build)
sourceMap <- view $ envConfigL . to (.envConfigSourceMap)
forMaybeM (Map.elems sourceMap.smDeps) $ \dp ->
case dp.dpLocation of
Expand All @@ -101,7 +101,7 @@ loadSourceMap smt boptsCli sma = do
bconfig <- view buildConfigL
let compiler = sma.smaCompiler
project = M.map applyOptsFlagsPP sma.smaProject
bopts = bconfig.bcConfig.configBuild
bopts = bconfig.bcConfig.build
applyOptsFlagsPP p@ProjectPackage{ppCommon = c} =
p{ppCommon = applyOptsFlags (M.member c.cpName smt.smtTargets) True c}
deps0 = smt.smtDeps <> sma.smaDeps
Expand Down Expand Up @@ -230,22 +230,22 @@ generalCabalConfigOpts ::
-> Bool
-> [Text]
generalCabalConfigOpts bconfig boptsCli name isTarget isLocal = concat
[ Map.findWithDefault [] CCKEverything config.configCabalConfigOpts
[ Map.findWithDefault [] CCKEverything config.cabalConfigOpts
, if isLocal
then Map.findWithDefault [] CCKLocals config.configCabalConfigOpts
then Map.findWithDefault [] CCKLocals config.cabalConfigOpts
else []
, if isTarget
then Map.findWithDefault [] CCKTargets config.configCabalConfigOpts
then Map.findWithDefault [] CCKTargets config.cabalConfigOpts
else []
, Map.findWithDefault [] (CCKPackage name) config.configCabalConfigOpts
, Map.findWithDefault [] (CCKPackage name) config.cabalConfigOpts
, if includeExtraOptions
then boptsCLIAllProgOptions boptsCli
else []
]
where
config = view configL bconfig
includeExtraOptions =
case config.configApplyProgOptions of
case config.applyProgOptions of
APOTargets -> isTarget
APOLocals -> isLocal
APOEverything -> True
Expand All @@ -254,12 +254,12 @@ generalCabalConfigOpts bconfig boptsCli name isTarget isLocal = concat
-- configuration and commandline.
generalGhcOptions :: BuildConfig -> BuildOptsCLI -> Bool -> Bool -> [Text]
generalGhcOptions bconfig boptsCli isTarget isLocal = concat
[ Map.findWithDefault [] AGOEverything config.configGhcOptionsByCat
[ Map.findWithDefault [] AGOEverything config.ghcOptionsByCat
, if isLocal
then Map.findWithDefault [] AGOLocals config.configGhcOptionsByCat
then Map.findWithDefault [] AGOLocals config.ghcOptionsByCat
else []
, if isTarget
then Map.findWithDefault [] AGOTargets config.configGhcOptionsByCat
then Map.findWithDefault [] AGOTargets config.ghcOptionsByCat
else []
, concat [["-fhpc"] | isLocal && bopts.boptsTestOpts.toCoverage]
, if bopts.boptsLibProfile || bopts.boptsExeProfile
Expand All @@ -271,10 +271,10 @@ generalGhcOptions bconfig boptsCli isTarget isLocal = concat
else []
]
where
bopts = config.configBuild
bopts = config.build
config = view configL bconfig
includeExtraOptions =
case config.configApplyGhcOptions of
case config.applyGhcOptions of
AGOTargets -> isTarget
AGOLocals -> isLocal
AGOEverything -> True
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 @@ -582,7 +582,7 @@ parseTargets needTargets haddockDeps boptscli smActual = do
}
where
bcImplicitGlobal bconfig =
case bconfig.bcConfig.configProject of
case bconfig.bcConfig.project of
PCProject _ -> False
PCGlobalProject -> True
PCNoProject _ -> False
2 changes: 1 addition & 1 deletion src/Stack/ComponentFile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -364,7 +364,7 @@ findCandidate ::
-> RIO GetPackageFileContext (Maybe DotCabalPath)
findCandidate dirs name = do
pkg <- asks (.ctxFile) >>= parsePackageNameFromFilePath
customPreprocessorExts <- view $ configL . to (.configCustomPreprocessorExts)
customPreprocessorExts <- view $ configL . to (.customPreprocessorExts)
let haskellPreprocessorExts =
haskellDefaultPreprocessorExts ++ customPreprocessorExts
candidates <- liftIO $ makeNameCandidates haskellPreprocessorExts
Expand Down
Loading

0 comments on commit 583275c

Please sign in to comment.