Skip to content

Commit 5ce326a

Browse files
committed
Remove unnecessary import of RIO qualified
Also, minor reformatting of same modules to be syntax-highlighter friendly.
1 parent cdc3cc1 commit 5ce326a

File tree

5 files changed

+197
-164
lines changed

5 files changed

+197
-164
lines changed

src/Stack/Build/ConstructPlan.hs

Lines changed: 13 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,8 @@
1010

1111
-- | Construct a @Plan@ for how to build
1212
module Stack.Build.ConstructPlan
13-
( constructPlan
14-
) where
13+
( constructPlan
14+
) where
1515

1616
import Control.Monad.RWS.Strict hiding ( (<>) )
1717
import Control.Monad.State.Strict ( execState )
@@ -25,7 +25,6 @@ import Distribution.Types.BuildType ( BuildType (Configure) )
2525
import Distribution.Types.PackageName ( mkPackageName )
2626
import Generics.Deriving.Monoid ( memptydefault, mappenddefault )
2727
import Path ( parent )
28-
import qualified RIO
2928
import RIO.Process ( findExecutable, HasProcessContext (..) )
3029
import Stack.Build.Cache
3130
import Stack.Build.Haddock
@@ -34,7 +33,7 @@ import Stack.Build.Source
3433
import Stack.Constants
3534
import Stack.Package
3635
import Stack.PackageDump
37-
import Stack.Prelude hiding ( Display (..), loadPackage )
36+
import Stack.Prelude hiding ( loadPackage )
3837
import Stack.SourceMap
3938
import Stack.Types.Build
4039
import Stack.Types.Compiler
@@ -186,7 +185,7 @@ constructPlan baseConfigOpts0 localDumpPkgs loadPackage0 sourceMap installedMap
186185
let ctx = mkCtx econfig globalCabalVersion sources mcur pathEnvVar'
187186
((), m, W efinals installExes dirtyReason warnings parents) <-
188187
liftIO $ runRWST inner ctx M.empty
189-
mapM_ (logWarn . RIO.display) (warnings [])
188+
mapM_ (logWarn . display) (warnings [])
190189
let toEither (_, Left e) = Left e
191190
toEither (k, Right v) = Right (k, v)
192191
(errlibs, adrs) = partitionEithers $ map toEither $ M.toList m
@@ -676,7 +675,15 @@ addEllipsis t
676675
-- then the parent package must be installed locally. Otherwise, if it
677676
-- is 'Snap', then it can either be installed locally or in the
678677
-- snapshot.
679-
addPackageDeps :: Package -> M (Either ConstructPlanException (Set PackageIdentifier, Map PackageIdentifier GhcPkgId, IsMutable))
678+
addPackageDeps ::
679+
Package
680+
-> M ( Either
681+
ConstructPlanException
682+
( Set PackageIdentifier
683+
, Map PackageIdentifier GhcPkgId
684+
, IsMutable
685+
)
686+
)
680687
addPackageDeps package = do
681688
ctx <- ask
682689
checkAndWarnForUnknownTools package

src/Stack/Build/Execute.hs

Lines changed: 51 additions & 47 deletions
Original file line numberDiff line numberDiff line change
@@ -12,21 +12,22 @@
1212

1313
-- | Perform a build
1414
module Stack.Build.Execute
15-
( printPlan
16-
, preFetch
17-
, executePlan
18-
-- * Running Setup.hs
19-
, ExecuteEnv
20-
, withExecuteEnv
21-
, withSingleContext
22-
, ExcludeTHLoading (..)
23-
, KeepOutputOpen (..)
24-
) where
15+
( printPlan
16+
, preFetch
17+
, executePlan
18+
-- * Running Setup.hs
19+
, ExecuteEnv
20+
, withExecuteEnv
21+
, withSingleContext
22+
, ExcludeTHLoading (..)
23+
, KeepOutputOpen (..)
24+
) where
2525

2626
import Control.Concurrent.Execute
2727
import Control.Concurrent.STM ( check )
2828
import Crypto.Hash
29-
import Data.Attoparsec.Text as P hiding ( try )
29+
import Data.Attoparsec.Text ( char, choice, digit, parseOnly )
30+
import qualified Data.Attoparsec.Text as P ( string )
3031
import qualified Data.ByteArray as Mem ( convert )
3132
import qualified Data.ByteString as S
3233
import qualified Data.ByteString.Builder
@@ -67,7 +68,6 @@ import Path.CheckInstall
6768
import Path.Extra ( toFilePathNoTrailingSep, rejectMissingFile )
6869
import Path.IO
6970
hiding ( findExecutable, makeAbsolute, withSystemTempDir )
70-
import qualified RIO
7171
import RIO.Process
7272
import Stack.Build.Cache
7373
import Stack.Build.Haddock
@@ -82,7 +82,7 @@ import Stack.DefaultColorWhen ( defaultColorWhen )
8282
import Stack.GhcPkg
8383
import Stack.Package
8484
import Stack.PackageDump
85-
import Stack.Prelude hiding ( Display (..) )
85+
import Stack.Prelude
8686
import Stack.Types.Build
8787
import Stack.Types.Compiler
8888
import Stack.Types.Config
@@ -116,7 +116,7 @@ preFetch plan
116116
| otherwise = do
117117
logDebug $
118118
"Prefetching: " <>
119-
mconcat (L.intersperse ", " (RIO.display <$> Set.toList pkgLocs))
119+
mconcat (L.intersperse ", " (display <$> Set.toList pkgLocs))
120120
fetchPackages pkgLocs
121121
where
122122
pkgLocs = Set.unions $ map toPkgLoc $ Map.elems $ planTasks plan
@@ -137,7 +137,7 @@ printPlan plan = do
137137
fromString (packageIdentifierString ident) <>
138138
if T.null reason
139139
then ""
140-
else " (" <> RIO.display reason <> ")"
140+
else " (" <> display reason <> ")"
141141

142142
logInfo ""
143143

@@ -168,7 +168,7 @@ printPlan plan = do
168168
xs -> do
169169
logInfo "Would install executables:"
170170
forM_ xs $ \(name, loc) -> logInfo $
171-
RIO.display name <>
171+
display name <>
172172
" from " <>
173173
(case loc of
174174
Snap -> "snapshot"
@@ -186,7 +186,7 @@ displayTask task =
186186
", source=" <>
187187
(case taskType task of
188188
TTLocalMutable lp -> fromString $ toFilePath $ parent $ lpCabalFile lp
189-
TTRemotePackage _ _ pl -> RIO.display pl) <>
189+
TTRemotePackage _ _ pl -> display pl) <>
190190
(if Set.null missing
191191
then ""
192192
else ", after: " <>
@@ -457,7 +457,7 @@ withExecuteEnv bopts boptsCli baseConfigOpts locals globalPackages snapshotPacka
457457
$ src
458458
.| CT.decodeUtf8Lenient
459459
.| mungeBuildOutput ExcludeTHLoading ConvertPathsToAbsolute pkgDir compilerVer
460-
.| CL.mapM_ (logInfo . RIO.display)
460+
.| CL.mapM_ (logInfo . display)
461461
logInfo $ "\n-- End of log file: " <> fromString (toFilePath filepath) <> "\n"
462462

463463
stripColors :: Path Abs File -> IO ()
@@ -519,8 +519,8 @@ executePlan boptsCli baseConfigOpts locals globalPackages snapshotPackages local
519519
Set.map (length . packageNameString) $
520520
Map.keysSet (planTasks plan) <> Map.keysSet (planFinals plan)
521521

522-
copyExecutables
523-
:: HasEnvConfig env
522+
copyExecutables ::
523+
HasEnvConfig env
524524
=> Map Text InstallLocation
525525
-> RIO env ()
526526
copyExecutables exes | Map.null exes = pure ()
@@ -554,7 +554,7 @@ copyExecutables exes = do
554554
Nothing -> do
555555
logWarn $
556556
"Couldn't find executable " <>
557-
RIO.display name <>
557+
display name <>
558558
" in directory " <>
559559
fromString (toFilePath bindir)
560560
pure Nothing
@@ -578,7 +578,7 @@ copyExecutables exes = do
578578
"Copied executables to " <>
579579
fromString destDir' <>
580580
":"
581-
forM_ installed $ \exe -> logInfo ("- " <> RIO.display exe)
581+
forM_ installed $ \exe -> logInfo ("- " <> display exe)
582582
unless compilerSpecific $ warnInstallSearchPathIssues destDir' installed
583583

584584

@@ -633,7 +633,7 @@ executePlan' installedMap0 targets plan ee@ExecuteEnv {..} = do
633633
let total = length actions
634634
loop prev
635635
| prev == total =
636-
run $ logStickyDone ("Completed " <> RIO.display total <> " action(s).")
636+
run $ logStickyDone ("Completed " <> display total <> " action(s).")
637637
| otherwise = do
638638
inProgress <- readTVarIO actionsVar
639639
let packageNames = map (\(ActionId pkgID _) -> pkgName pkgID) (toList inProgress)
@@ -642,7 +642,7 @@ executePlan' installedMap0 targets plan ee@ExecuteEnv {..} = do
642642
nowBuilding names = mconcat $ ": " : L.intersperse ", " (map (fromString . packageNameString) names)
643643
when terminal $ run $
644644
logSticky $
645-
"Progress " <> RIO.display prev <> "/" <> RIO.display total <>
645+
"Progress " <> display prev <> "/" <> display total <>
646646
nowBuilding packageNames
647647
done <- atomically $ do
648648
done <- readTVar doneVar
@@ -689,7 +689,7 @@ unregisterPackages cv localDB ids = do
689689
fromString (packageIdentifierString ident) <> ": unregistering" <>
690690
if T.null reason
691691
then ""
692-
else " (" <> RIO.display reason <> ")"
692+
else " (" <> display reason <> ")"
693693
let unregisterSinglePkg select (gid, (ident, reason)) = do
694694
logReason ident reason
695695
pkg <- getGhcPkgExe
@@ -987,7 +987,7 @@ packageNamePrefix ee name' =
987987
paddedName =
988988
case eeLargestPackageName ee of
989989
Nothing -> name
990-
Just len -> assert (len >= length name) $ RIO.take len $ name ++ L.repeat ' '
990+
Just len -> assert (len >= length name) $ take len $ name ++ L.repeat ' '
991991
in fromString paddedName <> "> "
992992

993993
announceTask :: HasLogFunc env => ExecuteEnv -> Task -> Utf8Builder -> RIO env ()
@@ -997,8 +997,8 @@ announceTask ee task action = logInfo $
997997

998998
-- | Ensure we're the only action using the directory. See
999999
-- <https://github.com/commercialhaskell/stack/issues/2730>
1000-
withLockedDistDir
1001-
:: HasEnvConfig env
1000+
withLockedDistDir ::
1001+
HasEnvConfig env
10021002
=> (Utf8Builder -> RIO env ()) -- ^ announce
10031003
-> Path Abs Dir -- ^ root directory for package
10041004
-> RIO env a
@@ -1146,8 +1146,8 @@ withSingleContext ActionContext {..} ee@ExecuteEnv {..} task@Task {..} allDeps m
11461146

11471147
withBinaryFile fp WriteMode $ \h -> inner $ OTLogFile logPath h
11481148

1149-
withCabal
1150-
:: Package
1149+
withCabal ::
1150+
Package
11511151
-> Path Abs Dir
11521152
-> OutputType
11531153
-> ((KeepOutputOpen -> ExcludeTHLoading -> [String] -> RIO env ()) -> RIO env a)
@@ -1309,8 +1309,8 @@ withSingleContext ActionContext {..} ee@ExecuteEnv {..} task@Task {..} allDeps m
13091309
void $ sinkProcessStderrStdout (toFilePath exeName) fullArgs
13101310
(outputSink KeepTHLoading LevelWarn compilerVer prefix)
13111311
(outputSink stripTHLoading LevelInfo compilerVer prefix)
1312-
outputSink
1313-
:: HasCallStack
1312+
outputSink ::
1313+
HasCallStack
13141314
=> ExcludeTHLoading
13151315
-> LogLevel
13161316
-> ActualCompiler
@@ -1319,7 +1319,7 @@ withSingleContext ActionContext {..} ee@ExecuteEnv {..} task@Task {..} allDeps m
13191319
outputSink excludeTH level compilerVer prefix =
13201320
CT.decodeUtf8Lenient
13211321
.| mungeBuildOutput excludeTH makeAbsolute pkgDir compilerVer
1322-
.| CL.mapM_ (logGeneric "" level . (prefix <>) . RIO.display)
1322+
.| CL.mapM_ (logGeneric "" level . (prefix <>) . display)
13231323
-- If users want control, we should add a config option for this
13241324
makeAbsolute :: ConvertPathsToAbsolute
13251325
makeAbsolute = case stripTHLoading of
@@ -1558,7 +1558,7 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
15581558
("Building all executables for `" <> fromString (packageNameString (packageName package)) <>
15591559
"' once. After a successful build of all of them, only specified executables will be rebuilt."))
15601560

1561-
_neededConfig <- ensureConfig cache pkgDir ee (announce ("configure" <> RIO.display (annSuffix executableBuildStatuses))) cabal cabalfp task
1561+
_neededConfig <- ensureConfig cache pkgDir ee (announce ("configure" <> display (annSuffix executableBuildStatuses))) cabal cabalfp task
15621562
let installedMapHasThisPkg :: Bool
15631563
installedMapHasThisPkg =
15641564
case Map.lookup (packageName package) installedMap of
@@ -1580,11 +1580,11 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
15801580
Just <$> realBuild cache package pkgDir cabal0 announce executableBuildStatuses
15811581

15821582
initialBuildSteps executableBuildStatuses cabal announce = do
1583-
announce ("initial-build-steps" <> RIO.display (annSuffix executableBuildStatuses))
1583+
announce ("initial-build-steps" <> display (annSuffix executableBuildStatuses))
15841584
cabal KeepTHLoading ["repl", "stack-initial-build-steps"]
15851585

1586-
realBuild
1587-
:: ConfigCache
1586+
realBuild ::
1587+
ConfigCache
15881588
-> Package
15891589
-> Path Abs Dir
15901590
-> (KeepOutputOpen -> ExcludeTHLoading -> [String] -> RIO env ())
@@ -1643,7 +1643,7 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
16431643
\to cause undefined reference errors from the \
16441644
\linker, along with other problems."
16451645

1646-
() <- announce ("build" <> RIO.display (annSuffix executableBuildStatuses))
1646+
() <- announce ("build" <> display (annSuffix executableBuildStatuses))
16471647
config <- view configL
16481648
extraOpts <- extraBuildOptions wc eeBuildOpts
16491649
let stripTHLoading
@@ -1811,8 +1811,8 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
18111811
-- .stack-work/dist/x86_64-osx/Cabal-1.22.4.0/build/alpha/alpha
18121812
-- .stack-work/dist/x86_64-osx/Cabal-1.22.4.0/build/alpha/alpha.exe
18131813
-- .stack-work/dist/x86_64-osx/Cabal-1.22.4.0/build/alpha/alpha.jsexe/ (NOTE: a dir)
1814-
getExecutableBuildStatuses
1815-
:: HasEnvConfig env
1814+
getExecutableBuildStatuses ::
1815+
HasEnvConfig env
18161816
=> Package -> Path Abs Dir -> RIO env (Map Text ExecutableBuildStatus)
18171817
getExecutableBuildStatuses package pkgDir = do
18181818
distDir <- distDirFromDir pkgDir
@@ -1822,8 +1822,8 @@ getExecutableBuildStatuses package pkgDir = do
18221822
(mapM (checkExeStatus platform distDir) (Set.toList (packageExes package)))
18231823

18241824
-- | Check whether the given executable is defined in the given dist directory.
1825-
checkExeStatus
1826-
:: HasLogFunc env
1825+
checkExeStatus ::
1826+
HasLogFunc env
18271827
=> Platform
18281828
-> Path b Dir
18291829
-> Text
@@ -1849,7 +1849,11 @@ checkExeStatus platform distDir name = do
18491849
file = T.unpack name
18501850

18511851
-- | Check if any unlisted files have been found, and add them to the build cache.
1852-
checkForUnlistedFiles :: HasEnvConfig env => TaskType -> Path Abs Dir -> RIO env [PackageWarning]
1852+
checkForUnlistedFiles ::
1853+
HasEnvConfig env
1854+
=> TaskType
1855+
-> Path Abs Dir
1856+
-> RIO env [PackageWarning]
18531857
checkForUnlistedFiles (TTLocalMutable lp) pkgDir = do
18541858
caches <- runMemoizedWith $ lpNewBuildCaches lp
18551859
(addBuildCache,warnings) <-
@@ -1973,7 +1977,7 @@ singleTest topts testsToRun ac ee task installedMap = do
19731977
"global-package-db\n" <>
19741978
"package-db " <> fromString snapDBPath <> "\n" <>
19751979
"package-db " <> fromString localDBPath <> "\n" <>
1976-
foldMap (\ghcId -> "package-id " <> RIO.display (unGhcPkgId ghcId) <> "\n")
1980+
foldMap (\ghcId -> "package-id " <> display (unGhcPkgId ghcId) <> "\n")
19771981
(pkgGhcIdList ++ thGhcId:M.elems allDepsMap)
19781982
writeFileUtf8Builder fp ghcEnv
19791983
menv <- liftIO $ setEnv fp =<< configProcessContextSettings config EnvSettings
@@ -1997,7 +2001,7 @@ singleTest topts testsToRun ac ee task installedMap = do
19972001
argsDisplay = case args of
19982002
[] -> ""
19992003
_ -> ", args: " <> T.intercalate " " (map showProcessArgDebug args)
2000-
announce $ "test (suite: " <> RIO.display testName <> RIO.display argsDisplay <> ")"
2004+
announce $ "test (suite: " <> display testName <> display argsDisplay <> ")"
20012005

20022006
-- Clear "Progress: ..." message before
20032007
-- redirecting output.
@@ -2016,7 +2020,7 @@ singleTest topts testsToRun ac ee task installedMap = do
20162020
CT.decodeUtf8Lenient .|
20172021
CT.lines .|
20182022
CL.map stripCR .|
2019-
CL.mapM_ (\t -> logInfo $ prefix <> RIO.display t))
2023+
CL.mapM_ (\t -> logInfo $ prefix <> display t))
20202024
createSource
20212025
OTLogFile _ h -> Nothing <$ useHandleOpen h
20222026
optionalTimeout action
@@ -2061,7 +2065,7 @@ singleTest topts testsToRun ac ee task installedMap = do
20612065
-- tidiness.
20622066
when needHpc $
20632067
updateTixFile (packageName package) tixPath testName'
2064-
let announceResult result = announce $ "Test suite " <> RIO.display testName <> " " <> result
2068+
let announceResult result = announce $ "Test suite " <> display testName <> " " <> result
20652069
case mec of
20662070
Just ExitSuccess -> do
20672071
announceResult "passed"

0 commit comments

Comments
 (0)