Skip to content

Commit 05c00ce

Browse files
committed
Eliminate ambiguity; make use of GHC2021's NamedFieldPuns
1 parent 05e3e6c commit 05c00ce

File tree

17 files changed

+291
-288
lines changed

17 files changed

+291
-288
lines changed

src/Stack/Build.hs

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -328,21 +328,21 @@ splitObjsWarning =
328328
-- | Get the @BaseConfigOpts@ necessary for constructing configure options
329329
mkBaseConfigOpts :: (HasEnvConfig env)
330330
=> BuildOptsCLI -> RIO env BaseConfigOpts
331-
mkBaseConfigOpts boptsCli = do
332-
bopts <- view buildOptsL
333-
snapDBPath <- packageDatabaseDeps
334-
localDBPath <- packageDatabaseLocal
331+
mkBaseConfigOpts buildOptsCLI = do
332+
buildOpts <- view buildOptsL
333+
snapDB <- packageDatabaseDeps
334+
localDB <- packageDatabaseLocal
335335
snapInstallRoot <- installationRootDeps
336336
localInstallRoot <- installationRootLocal
337-
packageExtraDBs <- packageDatabaseExtra
337+
extraDBs <- packageDatabaseExtra
338338
pure BaseConfigOpts
339-
{ snapDB = snapDBPath
340-
, localDB = localDBPath
341-
, snapInstallRoot = snapInstallRoot
342-
, localInstallRoot = localInstallRoot
343-
, buildOpts = bopts
344-
, buildOptsCLI = boptsCli
345-
, extraDBs = packageExtraDBs
339+
{ snapDB
340+
, localDB
341+
, snapInstallRoot
342+
, localInstallRoot
343+
, buildOpts
344+
, buildOptsCLI
345+
, extraDBs
346346
}
347347

348348
-- | Provide a function for loading package information from the package index
@@ -354,16 +354,16 @@ loadPackage ::
354354
-> [Text] -- ^ Cabal configure options
355355
-> RIO env Package
356356
loadPackage loc flags ghcOptions cabalConfigOpts = do
357-
compiler <- view actualCompilerVersionL
357+
compilerVersion <- view actualCompilerVersionL
358358
platform <- view platformL
359359
let pkgConfig = PackageConfig
360360
{ enableTests = False
361361
, enableBenchmarks = False
362-
, flags = flags
363-
, ghcOptions = ghcOptions
364-
, cabalConfigOpts = cabalConfigOpts
365-
, compilerVersion = compiler
366-
, platform = platform
362+
, flags
363+
, ghcOptions
364+
, cabalConfigOpts
365+
, compilerVersion
366+
, platform
367367
}
368368
resolvePackage pkgConfig <$> loadCabalFileImmutable loc
369369

src/Stack/Build/ExecuteEnv.hs

Lines changed: 87 additions & 80 deletions
Original file line numberDiff line numberDiff line change
@@ -261,90 +261,97 @@ withExecuteEnv ::
261261
-> Maybe Int -- ^ largest package name, for nicer interleaved output
262262
-> (ExecuteEnv -> RIO env a)
263263
-> RIO env a
264-
withExecuteEnv bopts boptsCli baseConfigOpts locals globalPackages snapshotPackages localPackages mlargestPackageName inner =
265-
createTempDirFunction stackProgName $ \tmpdir -> do
266-
installLock <- liftIO $ newMVar ()
267-
idMap <- liftIO $ newTVarIO Map.empty
268-
config <- view configL
269-
270-
customBuiltRef <- newIORef Set.empty
271-
272-
-- Create files for simple setup and setup shim, if necessary
273-
let setupSrcDir =
274-
view stackRootL config </>
275-
relDirSetupExeSrc
276-
ensureDir setupSrcDir
277-
let setupStub = "setup-" ++ simpleSetupHash
278-
setupFileName <- parseRelFile (setupStub ++ ".hs")
279-
setupHiName <- parseRelFile (setupStub ++ ".hi")
280-
setupOName <- parseRelFile (setupStub ++ ".o")
281-
let setupHs = setupSrcDir </> setupFileName
282-
setupHi = setupSrcDir </> setupHiName
283-
setupO = setupSrcDir </> setupOName
284-
setupHsExists <- doesFileExist setupHs
285-
unless setupHsExists $ writeBinaryFileAtomic setupHs simpleSetupCode
286-
-- See https://github.com/commercialhaskell/stack/issues/6267. Remove any
287-
-- historical *.hi or *.o files. This can be dropped when Stack drops
288-
-- support for the problematic versions of GHC.
289-
ignoringAbsence (removeFile setupHi)
290-
ignoringAbsence (removeFile setupO)
291-
let setupShimStub = "setup-shim-" ++ simpleSetupHash
292-
setupShimFileName <- parseRelFile (setupShimStub ++ ".hs")
293-
setupShimHiName <- parseRelFile (setupShimStub ++ ".hi")
294-
setupShimOName <- parseRelFile (setupShimStub ++ ".o")
295-
let setupShimHs = setupSrcDir </> setupShimFileName
296-
setupShimHi = setupSrcDir </> setupShimHiName
297-
setupShimO = setupSrcDir </> setupShimOName
298-
setupShimHsExists <- doesFileExist setupShimHs
299-
unless setupShimHsExists $
300-
writeBinaryFileAtomic setupShimHs setupGhciShimCode
301-
-- See https://github.com/commercialhaskell/stack/issues/6267. Remove any
302-
-- historical *.hi or *.o files. This can be dropped when Stack drops
303-
-- support for the problematic versions of GHC.
304-
ignoringAbsence (removeFile setupShimHi)
305-
ignoringAbsence (removeFile setupShimO)
306-
setupExe <- getSetupExe setupHs setupShimHs tmpdir
307-
308-
cabalPkgVer <- view cabalVersionL
309-
globalDB <- view $ compilerPathsL . to (.globalDB)
310-
snapshotPackagesTVar <-
311-
liftIO $ newTVarIO (toDumpPackagesByGhcPkgId snapshotPackages)
312-
localPackagesTVar <-
313-
liftIO $ newTVarIO (toDumpPackagesByGhcPkgId localPackages)
314-
logFilesTChan <- liftIO $ atomically newTChan
315-
let totalWanted = length $ filter (.wanted) locals
316-
pathEnvVar <- liftIO $ maybe mempty T.pack <$> lookupEnv "PATH"
317-
inner ExecuteEnv
318-
{ buildOpts = bopts
319-
, buildOptsCLI = boptsCli
320-
-- Uncertain as to why we cannot run configures in parallel. This
321-
-- appears to be a Cabal library bug. Original issue:
322-
-- https://github.com/commercialhaskell/stack/issues/84. Ideally
323-
-- we'd be able to remove this.
324-
, installLock = installLock
325-
, baseConfigOpts = baseConfigOpts
326-
, ghcPkgIds = idMap
327-
, tempDir = tmpdir
328-
, setupHs = setupHs
329-
, setupShimHs = setupShimHs
330-
, setupExe = setupExe
331-
, cabalPkgVer = cabalPkgVer
332-
, totalWanted = totalWanted
333-
, locals = locals
334-
, globalDB = globalDB
335-
, globalDumpPkgs = toDumpPackagesByGhcPkgId globalPackages
336-
, snapshotDumpPkgs = snapshotPackagesTVar
337-
, localDumpPkgs = localPackagesTVar
338-
, logFiles = logFilesTChan
339-
, customBuilt = customBuiltRef
340-
, largestPackageName = mlargestPackageName
341-
, pathEnvVar = pathEnvVar
342-
} `finally` dumpLogs logFilesTChan totalWanted
264+
withExecuteEnv
265+
buildOpts
266+
buildOptsCLI
267+
baseConfigOpts
268+
locals
269+
globalPackages
270+
snapshotPackages
271+
localPackages
272+
largestPackageName
273+
inner
274+
= createTempDirFunction stackProgName $ \tempDir -> do
275+
installLock <- liftIO $ newMVar ()
276+
ghcPkgIds <- liftIO $ newTVarIO Map.empty
277+
config <- view configL
278+
customBuilt <- newIORef Set.empty
279+
-- Create files for simple setup and setup shim, if necessary
280+
let setupSrcDir =
281+
view stackRootL config </>
282+
relDirSetupExeSrc
283+
ensureDir setupSrcDir
284+
let setupStub = "setup-" ++ simpleSetupHash
285+
setupFileName <- parseRelFile (setupStub ++ ".hs")
286+
setupHiName <- parseRelFile (setupStub ++ ".hi")
287+
setupOName <- parseRelFile (setupStub ++ ".o")
288+
let setupHs = setupSrcDir </> setupFileName
289+
setupHi = setupSrcDir </> setupHiName
290+
setupO = setupSrcDir </> setupOName
291+
setupHsExists <- doesFileExist setupHs
292+
unless setupHsExists $ writeBinaryFileAtomic setupHs simpleSetupCode
293+
-- See https://github.com/commercialhaskell/stack/issues/6267. Remove any
294+
-- historical *.hi or *.o files. This can be dropped when Stack drops
295+
-- support for the problematic versions of GHC.
296+
ignoringAbsence (removeFile setupHi)
297+
ignoringAbsence (removeFile setupO)
298+
let setupShimStub = "setup-shim-" ++ simpleSetupHash
299+
setupShimFileName <- parseRelFile (setupShimStub ++ ".hs")
300+
setupShimHiName <- parseRelFile (setupShimStub ++ ".hi")
301+
setupShimOName <- parseRelFile (setupShimStub ++ ".o")
302+
let setupShimHs = setupSrcDir </> setupShimFileName
303+
setupShimHi = setupSrcDir </> setupShimHiName
304+
setupShimO = setupSrcDir </> setupShimOName
305+
setupShimHsExists <- doesFileExist setupShimHs
306+
unless setupShimHsExists $
307+
writeBinaryFileAtomic setupShimHs setupGhciShimCode
308+
-- See https://github.com/commercialhaskell/stack/issues/6267. Remove any
309+
-- historical *.hi or *.o files. This can be dropped when Stack drops
310+
-- support for the problematic versions of GHC.
311+
ignoringAbsence (removeFile setupShimHi)
312+
ignoringAbsence (removeFile setupShimO)
313+
setupExe <- getSetupExe setupHs setupShimHs tempDir
314+
cabalPkgVer <- view cabalVersionL
315+
globalDB <- view $ compilerPathsL . to (.globalDB)
316+
let globalDumpPkgs = toDumpPackagesByGhcPkgId globalPackages
317+
snapshotDumpPkgs <-
318+
liftIO $ newTVarIO (toDumpPackagesByGhcPkgId snapshotPackages)
319+
localDumpPkgs <-
320+
liftIO $ newTVarIO (toDumpPackagesByGhcPkgId localPackages)
321+
logFiles <- liftIO $ atomically newTChan
322+
let totalWanted = length $ filter (.wanted) locals
323+
pathEnvVar <- liftIO $ maybe mempty T.pack <$> lookupEnv "PATH"
324+
inner ExecuteEnv
325+
{ buildOpts
326+
, buildOptsCLI
327+
-- Uncertain as to why we cannot run configures in parallel. This
328+
-- appears to be a Cabal library bug. Original issue:
329+
-- https://github.com/commercialhaskell/stack/issues/84. Ideally
330+
-- we'd be able to remove this.
331+
, installLock
332+
, baseConfigOpts
333+
, ghcPkgIds
334+
, tempDir
335+
, setupHs
336+
, setupShimHs
337+
, setupExe
338+
, cabalPkgVer
339+
, totalWanted
340+
, locals
341+
, globalDB
342+
, globalDumpPkgs
343+
, snapshotDumpPkgs
344+
, localDumpPkgs
345+
, logFiles
346+
, customBuilt
347+
, largestPackageName
348+
, pathEnvVar
349+
} `finally` dumpLogs logFiles totalWanted
343350
where
344351
toDumpPackagesByGhcPkgId = Map.fromList . map (\dp -> (dp.ghcPkgId, dp))
345352

346353
createTempDirFunction
347-
| bopts.keepTmpFiles = withKeepSystemTempDir
354+
| buildOpts.keepTmpFiles = withKeepSystemTempDir
348355
| otherwise = withSystemTempDir
349356

350357
dumpLogs :: TChan (Path Abs Dir, Path Abs File) -> Int -> RIO env ()

src/Stack/Build/Source.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -415,11 +415,11 @@ loadLocalPackage pp = do
415415
pure LocalPackage
416416
{ package = pkg
417417
, testBench = btpkg
418-
, componentFiles = componentFiles
418+
, componentFiles
419419
, buildHaddocks = pp.common.haddocks
420420
, forceDirty = bopts.forceDirty
421-
, dirtyFiles = dirtyFiles
422-
, newBuildCaches = newBuildCaches
421+
, dirtyFiles
422+
, newBuildCaches
423423
, cabalFile = pp.cabalFP
424424
, wanted = isWanted
425425
, components = nonLibComponents

src/Stack/BuildPlan.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -166,7 +166,7 @@ gpdPackageDeps ::
166166
-> Platform
167167
-> Map FlagName Bool
168168
-> Map PackageName VersionRange
169-
gpdPackageDeps gpd ac platform flags =
169+
gpdPackageDeps gpd compilerVersion platform flags =
170170
Map.filterWithKey (const . not . isLocalLibrary) (packageDependencies pkgDesc)
171171
where
172172
isLocalLibrary name' = name' == name || name' `Set.member` subs
@@ -182,11 +182,11 @@ gpdPackageDeps gpd ac platform flags =
182182
pkgConfig = PackageConfig
183183
{ enableTests = True
184184
, enableBenchmarks = True
185-
, flags = flags
185+
, flags
186186
, ghcOptions = []
187187
, cabalConfigOpts = []
188-
, compilerVersion = ac
189-
, platform = platform
188+
, compilerVersion
189+
, platform
190190
}
191191

192192
-- Remove any src package flags having default values

src/Stack/Config.hs

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -727,7 +727,7 @@ withBuildConfig inner = do
727727
logDebug ("Using resolver: " <> display aresolver <> " specified on command line")
728728
makeConcreteResolver aresolver
729729

730-
(project', stackYamlFP) <- case config.project of
730+
(project', stackYaml) <- case config.project of
731731
PCProject (project, fp) -> do
732732
forM_ project.userMsg prettyWarnS
733733
pure (project, fp)
@@ -794,22 +794,22 @@ withBuildConfig inner = do
794794
}
795795
extraPackageDBs <- mapM resolveDir' project.extraPackageDBs
796796

797-
wanted <- lockCachedWanted stackYamlFP project.resolver $
798-
fillProjectWanted stackYamlFP config project
797+
smWanted <- lockCachedWanted stackYaml project.resolver $
798+
fillProjectWanted stackYaml config project
799799

800800
-- Unfortunately redoes getProjectWorkDir, since we don't have a BuildConfig
801801
-- yet
802802
workDir <- view workDirL
803-
let projectStorageFile = parent stackYamlFP </> workDir </> relFileStorage
803+
let projectStorageFile = parent stackYaml </> workDir </> relFileStorage
804804

805805
initProjectStorage projectStorageFile $ \projectStorage -> do
806806
let bc = BuildConfig
807-
{ config = config
808-
, smWanted = wanted
809-
, extraPackageDBs = extraPackageDBs
810-
, stackYaml = stackYamlFP
807+
{ config
808+
, smWanted
809+
, extraPackageDBs
810+
, stackYaml
811811
, curator = project.curator
812-
, projectStorage = projectStorage
812+
, projectStorage
813813
}
814814
runRIO bc inner
815815
where
@@ -836,8 +836,7 @@ withBuildConfig inner = do
836836
pure Project
837837
{ userMsg = Nothing
838838
, packages = []
839-
, dependencies =
840-
map (RPLImmutable . flip RPLIHackage Nothing) extraDeps
839+
, dependencies = map (RPLImmutable . flip RPLIHackage Nothing) extraDeps
841840
, flags = mempty
842841
, resolver = r
843842
, compiler = Nothing

src/Stack/Options/ConfigParser.hs

Lines changed: 31 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ import Stack.Options.GhcBuildParser ( ghcBuildParser )
2424
import Stack.Options.GhcVariantParser ( ghcVariantParser )
2525
import Stack.Options.NixParser ( nixOptsParser )
2626
import Stack.Options.Utils ( GlobalOptsContext (..), hideMods )
27-
import Stack.Prelude
27+
import Stack.Prelude hiding ( snapshotLocation )
2828
import Stack.Types.ColorWhen ( readColorWhen )
2929
import Stack.Types.ConfigMonoid ( ConfigMonoid (..) )
3030
import Stack.Types.DumpLogs ( DumpLogs (..) )
@@ -34,35 +34,36 @@ import qualified System.FilePath as FilePath
3434
configOptsParser :: FilePath -> GlobalOptsContext -> Parser ConfigMonoid
3535
configOptsParser currentDir hide0 =
3636
( \stackRoot workDir buildOpts dockerOpts nixOpts systemGHC installGHC arch
37-
ghcVariant ghcBuild jobs includes libs preprocs overrideGccPath overrideHpack
38-
skipGHCCheck skipMsys localBin setupInfoLocations modifyCodePage
39-
allowDifferentUser dumpLogs colorWhen snapLoc noRunCompile -> mempty
40-
{ stackRoot = stackRoot
41-
, workDir = workDir
42-
, buildOpts = buildOpts
43-
, dockerOpts = dockerOpts
44-
, nixOpts = nixOpts
45-
, systemGHC = systemGHC
46-
, installGHC = installGHC
47-
, skipGHCCheck = skipGHCCheck
48-
, arch = arch
49-
, ghcVariant = ghcVariant
50-
, ghcBuild = ghcBuild
51-
, jobs = jobs
52-
, extraIncludeDirs = includes
53-
, extraLibDirs = libs
54-
, customPreprocessorExts = preprocs
55-
, overrideGccPath = overrideGccPath
56-
, overrideHpack = overrideHpack
57-
, skipMsys = skipMsys
58-
, localBinPath = localBin
59-
, setupInfoLocations = setupInfoLocations
60-
, modifyCodePage = modifyCodePage
61-
, allowDifferentUser = allowDifferentUser
62-
, dumpLogs = dumpLogs
63-
, colorWhen = colorWhen
64-
, snapshotLocation = snapLoc
65-
, noRunCompile = noRunCompile
37+
ghcVariant ghcBuild jobs extraIncludeDirs extraLibDirs
38+
customPreprocessorExts overrideGccPath overrideHpack skipGHCCheck skipMsys
39+
localBinPath setupInfoLocations modifyCodePage allowDifferentUser dumpLogs
40+
colorWhen snapshotLocation noRunCompile -> mempty
41+
{ stackRoot
42+
, workDir
43+
, buildOpts
44+
, dockerOpts
45+
, nixOpts
46+
, systemGHC
47+
, installGHC
48+
, skipGHCCheck
49+
, arch
50+
, ghcVariant
51+
, ghcBuild
52+
, jobs
53+
, extraIncludeDirs
54+
, extraLibDirs
55+
, customPreprocessorExts
56+
, overrideGccPath
57+
, overrideHpack
58+
, skipMsys
59+
, localBinPath
60+
, setupInfoLocations
61+
, modifyCodePage
62+
, allowDifferentUser
63+
, dumpLogs
64+
, colorWhen
65+
, snapshotLocation
66+
, noRunCompile
6667
}
6768
)
6869
<$> optionalFirst (absDirOption

0 commit comments

Comments
 (0)