Skip to content

Commit a9b498d

Browse files
authored
Merge pull request #5883 from Vlix/import-data-list-qualified
import `Data.List` qualified as "-Wcompat-unqualified-imports" says
2 parents ce5b9e4 + fe73099 commit a9b498d

File tree

14 files changed

+72
-72
lines changed

14 files changed

+72
-72
lines changed

src/Path/Find.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module Path.Find
1212

1313
import RIO
1414
import System.IO.Error (isPermissionError)
15-
import Data.List
15+
import qualified Data.List as L
1616
import Path
1717
import Path.IO hiding (findFiles)
1818
import System.PosixCompat.Files (getSymbolicLinkStatus, isSymbolicLink)
@@ -43,7 +43,7 @@ findPathUp :: (MonadIO m,MonadThrow m)
4343
-> m (Maybe (Path Abs t)) -- ^ Absolute path.
4444
findPathUp pathType dir p upperBound =
4545
do entries <- listDir dir
46-
case find p (pathType entries) of
46+
case L.find p (pathType entries) of
4747
Just path -> pure (Just path)
4848
Nothing | Just dir == upperBound -> pure Nothing
4949
| parent dir == dir -> pure Nothing

src/Stack/Build/ConstructPlan.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ module Stack.Build.ConstructPlan
1717
import Stack.Prelude hiding (Display (..), loadPackage)
1818
import Control.Monad.RWS.Strict hiding ((<>))
1919
import Control.Monad.State.Strict (execState)
20-
import Data.List
20+
import qualified Data.List as L
2121
import qualified Data.Map.Strict as M
2222
import qualified Data.Map.Strict as Map
2323
import Data.Monoid.Map (MonoidMap(..))
@@ -285,12 +285,12 @@ instance Show NotOnlyLocal where
285285
[ "Specified only-locals, but I need to build snapshot contents:\n"
286286
, if null packages then "" else concat
287287
[ "Packages: "
288-
, intercalate ", " (map packageNameString packages)
288+
, L.intercalate ", " (map packageNameString packages)
289289
, "\n"
290290
]
291291
, if null exes then "" else concat
292292
[ "Executables: "
293-
, intercalate ", " (map T.unpack exes)
293+
, L.intercalate ", " (map T.unpack exes)
294294
, "\n"
295295
]
296296
]
@@ -1037,7 +1037,7 @@ pprintExceptions exceptions stackYaml stackRoot parentMap wanted' prunedGlobalDe
10371037
mconcat $
10381038
[ flow "While constructing the build plan, the following exceptions were encountered:"
10391039
, line <> line
1040-
, mconcat (intersperse (line <> line) (mapMaybe pprintException exceptions'))
1040+
, mconcat (L.intersperse (line <> line) (mapMaybe pprintException exceptions'))
10411041
, line <> line
10421042
, flow "Some different approaches to resolving this:"
10431043
, line <> line
@@ -1173,7 +1173,7 @@ pprintExceptions exceptions stackYaml stackRoot parentMap wanted' prunedGlobalDe
11731173
align (flow "is a library dependency, but the package provides no library")
11741174
BDDependencyCycleDetected names -> Just $
11751175
style Error (fromString $ packageNameString name) <+>
1176-
align (flow $ "dependency cycle detected: " ++ intercalate ", " (map packageNameString names))
1176+
align (flow $ "dependency cycle detected: " ++ L.intercalate ", " (map packageNameString names))
11771177
where
11781178
goodRange = style Good (fromString (Cabal.display range))
11791179
latestApplicable mversion =
@@ -1215,9 +1215,9 @@ getShortestDepsPath (MonoidMap parentsMap) wanted' name =
12151215
findShortest fuel paths =
12161216
case targets of
12171217
[] -> findShortest (fuel - 1) $ M.fromListWith chooseBest $ concatMap extendPath recurses
1218-
_ -> let (DepsPath _ _ path) = minimum (map snd targets) in path
1218+
_ -> let (DepsPath _ _ path) = L.minimum (map snd targets) in path
12191219
where
1220-
(targets, recurses) = partition (\(n, _) -> n `Set.member` wanted') (M.toList paths)
1220+
(targets, recurses) = L.partition (\(n, _) -> n `Set.member` wanted') (M.toList paths)
12211221
chooseBest :: DepsPath -> DepsPath -> DepsPath
12221222
chooseBest x y = max x y
12231223
-- Extend a path to all its parents.

src/Stack/Build/Execute.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ import qualified Data.Conduit.Filesystem as CF
4040
import qualified Data.Conduit.List as CL
4141
import Data.Conduit.Process.Typed (createSource)
4242
import qualified Data.Conduit.Text as CT
43-
import Data.List hiding (any)
43+
import qualified Data.List as L
4444
import Data.List.NonEmpty (nonEmpty)
4545
import qualified Data.List.NonEmpty as NonEmpty (toList)
4646
import Data.List.Split (chunksOf)
@@ -110,7 +110,7 @@ preFetch plan
110110
| otherwise = do
111111
logDebug $
112112
"Prefetching: " <>
113-
mconcat (intersperse ", " (RIO.display <$> Set.toList pkgLocs))
113+
mconcat (L.intersperse ", " (RIO.display <$> Set.toList pkgLocs))
114114
fetchPackages pkgLocs
115115
where
116116
pkgLocs = Set.unions $ map toPkgLoc $ Map.elems $ planTasks plan
@@ -184,7 +184,7 @@ displayTask task =
184184
(if Set.null missing
185185
then ""
186186
else ", after: " <>
187-
mconcat (intersperse "," (fromString . packageIdentifierString <$> Set.toList missing)))
187+
mconcat (L.intersperse "," (fromString . packageIdentifierString <$> Set.toList missing)))
188188
where
189189
missing = tcoMissing $ taskConfigOpts task
190190

@@ -626,7 +626,7 @@ executePlan' installedMap0 targets plan ee@ExecuteEnv {..} = do
626626
let packageNames = map (\(ActionId pkgID _) -> pkgName pkgID) (toList inProgress)
627627
nowBuilding :: [PackageName] -> Utf8Builder
628628
nowBuilding [] = ""
629-
nowBuilding names = mconcat $ ": " : intersperse ", " (map (fromString . packageNameString) names)
629+
nowBuilding names = mconcat $ ": " : L.intersperse ", " (map (fromString . packageNameString) names)
630630
when terminal $ run $
631631
logSticky $
632632
"Progress " <> RIO.display prev <> "/" <> RIO.display total <>
@@ -974,7 +974,7 @@ packageNamePrefix ee name' =
974974
paddedName =
975975
case eeLargestPackageName ee of
976976
Nothing -> name
977-
Just len -> assert (len >= length name) $ RIO.take len $ name ++ repeat ' '
977+
Just len -> assert (len >= length name) $ RIO.take len $ name ++ L.repeat ' '
978978
in fromString paddedName <> "> "
979979

980980
announceTask :: HasLogFunc env => ExecuteEnv -> Task -> Utf8Builder -> RIO env ()
@@ -1608,12 +1608,12 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
16081608
"- In" <+>
16091609
fromString (T.unpack (renderComponent comp)) <>
16101610
":" <> line <>
1611-
indent 4 (mconcat $ intersperse line $ map (style Good . fromString . C.display) modules)
1611+
indent 4 (mconcat $ L.intersperse line $ map (style Good . fromString . C.display) modules)
16121612
forM_ mlocalWarnings $ \(cabalfp, warnings) -> do
16131613
unless (null warnings) $ prettyWarn $
16141614
"The following modules should be added to exposed-modules or other-modules in" <+>
16151615
pretty cabalfp <> ":" <> line <>
1616-
indent 4 (mconcat $ intersperse line $ map showModuleWarning warnings) <>
1616+
indent 4 (mconcat $ L.intersperse line $ map showModuleWarning warnings) <>
16171617
line <> line <>
16181618
"Missing modules in the cabal file are likely to cause undefined reference errors from the linker, along with other problems."
16191619

@@ -1705,12 +1705,12 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
17051705

17061706
runConduitRes
17071707
$ CF.sourceDirectoryDeep False (toFilePath distDir)
1708-
.| CL.filter (isInfixOf ".dump-")
1708+
.| CL.filter (L.isInfixOf ".dump-")
17091709
.| CL.mapM_ (\src -> liftIO $ do
17101710
parentDir <- parent <$> parseRelDir src
17111711
destBaseDir <- (ddumpDir </>) <$> stripProperPrefix distDir parentDir
17121712
-- exclude .stack-work dir
1713-
unless (".stack-work" `isInfixOf` toFilePath destBaseDir) $ do
1713+
unless (".stack-work" `L.isInfixOf` toFilePath destBaseDir) $ do
17141714
ensureDir destBaseDir
17151715
src' <- parseRelFile src
17161716
copyFile src' (destBaseDir </> filename src'))
@@ -1919,7 +1919,7 @@ singleTest topts testsToRun ac ee task installedMap = do
19191919
Just (Library _ ghcPkgId _) -> [ghcPkgId]
19201920
_ -> []
19211921
-- doctest relies on template-haskell in QuickCheck-based tests
1922-
thGhcId <- case find ((== "template-haskell") . pkgName . dpPackageIdent. snd)
1922+
thGhcId <- case L.find ((== "template-haskell") . pkgName . dpPackageIdent. snd)
19231923
(Map.toList $ eeGlobalDumpPkgs ee) of
19241924
Just (ghcId, _) -> pure ghcId
19251925
Nothing -> error "template-haskell is a wired-in GHC boot library but it wasn't found"

src/Stack/Build/Installed.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@ module Stack.Build.Installed
1616
import Data.Conduit
1717
import qualified Data.Conduit.List as CL
1818
import qualified Data.Set as Set
19-
import Data.List
2019
import qualified Data.Map.Strict as Map
2120
import Path
2221
import Stack.Build.Cache

src/Stack/Build/Source.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import qualified Pantry.SHA256 as SHA256
2323
import Data.ByteString.Builder (toLazyByteString)
2424
import Conduit (ZipSink (..), withSourceFile)
2525
import qualified Distribution.PackageDescription as C
26-
import Data.List
26+
import qualified Data.List as L
2727
import qualified Data.Map as Map
2828
import qualified Data.Map.Strict as M
2929
import qualified Data.Set as Set
@@ -363,7 +363,7 @@ loadLocalPackage pp = do
363363
pure $
364364
if not (Set.null allDirtyFiles)
365365
then let tryStripPrefix y =
366-
fromMaybe y (stripPrefix (toFilePath $ ppRoot pp) y)
366+
fromMaybe y (L.stripPrefix (toFilePath $ ppRoot pp) y)
367367
in Just $ Set.map tryStripPrefix allDirtyFiles
368368
else Nothing
369369
newBuildCaches =

src/Stack/Coverage.hs

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ module Stack.Coverage
2121
import Stack.Prelude hiding (Display (..))
2222
import qualified Data.ByteString.Char8 as S8
2323
import qualified Data.ByteString.Lazy as BL
24-
import Data.List
24+
import qualified Data.List as L
2525
import qualified Data.Map.Strict as Map
2626
import qualified Data.Set as Set
2727
import qualified Data.Text as T
@@ -141,8 +141,9 @@ generateHpcReport pkgDir package tests = do
141141
-- #634 - this will likely be customizable in the future)
142142
Right mincludeName -> do
143143
let extraArgs = case mincludeName of
144-
Just includeNames -> "--include" : intersperse "--include" (map (\n -> n ++ ":") includeNames)
145144
Nothing -> []
145+
Just includeNames ->
146+
"--include" : L.intersperse "--include" (map (\n -> n ++ ":") includeNames)
146147
mreportPath <- generateHpcReportInternal tixSrc reportDir report extraArgs extraArgs
147148
forM_ mreportPath (displayReportPath "The" report . pretty)
148149

@@ -254,7 +255,7 @@ generateHpcReportForTargets opts tixFiles targetNames = do
254255
(dirs, _) <- listDir pkgPath
255256
liftM concat $ forM dirs $ \dir -> do
256257
(_, files) <- listDir dir
257-
pure (filter ((".tix" `isSuffixOf`) . toFilePath) files)
258+
pure (filter ((".tix" `L.isSuffixOf`) . toFilePath) files)
258259
else pure []
259260
tixPaths <- liftM (\xs -> xs ++ targetTixFiles) $ mapM (resolveFile' . T.unpack) tixFiles
260261
when (null tixPaths) $
@@ -284,7 +285,7 @@ generateHpcUnifiedReport = do
284285
(dirs', _) <- listDir dir
285286
forM dirs' $ \dir' -> do
286287
(_, files) <- listDir dir'
287-
pure (filter ((".tix" `isSuffixOf`) . toFilePath) files)
288+
pure (filter ((".tix" `L.isSuffixOf`) . toFilePath) files)
288289
extraTixFiles <- findExtraTixFiles
289290
let tixFiles = tixFiles0 ++ extraTixFiles
290291
reportDir = outputDir </> relDirCombined </> relDirAll
@@ -324,7 +325,7 @@ generateUnionReport report reportDir tixFiles = do
324325
"The following modules are left out of the " <>
325326
RIO.display report <>
326327
" due to version mismatches: " <>
327-
mconcat (intersperse ", " (map fromString errs))
328+
mconcat (L.intersperse ", " (map fromString errs))
328329
tixDest <- liftM (reportDir </>) $ parseRelFile (dirnameString reportDir ++ ".tix")
329330
ensureDir (parent tixDest)
330331
liftIO $ writeTix (toFilePath tixDest) tix
@@ -435,7 +436,7 @@ sanitize :: String -> Text
435436
sanitize = LT.toStrict . htmlEscape . LT.pack
436437

437438
dirnameString :: Path r Dir -> String
438-
dirnameString = dropWhileEnd isPathSeparator . toFilePath . dirname
439+
dirnameString = L.dropWhileEnd isPathSeparator . toFilePath . dirname
439440

440441
findPackageFieldForBuiltPackage
441442
:: HasEnvConfig env
@@ -506,5 +507,5 @@ findExtraTixFiles = do
506507
if dirExists
507508
then do
508509
(_, files) <- listDir dir
509-
pure $ filter ((".tix" `isSuffixOf`) . toFilePath) files
510+
pure $ filter ((".tix" `L.isSuffixOf`) . toFilePath) files
510511
else pure []

src/Stack/GhcPkg.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ module Stack.GhcPkg
1717
import Stack.Prelude
1818
import qualified Data.ByteString.Char8 as S8
1919
import qualified Data.ByteString.Lazy as BL
20-
import Data.List
20+
import qualified Data.List as L
2121
import qualified Data.Text as T
2222
import qualified Data.Text.Encoding as T
2323
import Path (parent, (</>))
@@ -152,7 +152,7 @@ unregisterGhcPkgIds pkgexe pkgDb epgids = do
152152
-- | Get the value for GHC_PACKAGE_PATH
153153
mkGhcPackagePath :: Bool -> Path Abs Dir -> Path Abs Dir -> [Path Abs Dir] -> Path Abs Dir -> Text
154154
mkGhcPackagePath locals localdb deps extras globaldb =
155-
T.pack $ intercalate [searchPathSeparator] $ concat
155+
T.pack $ L.intercalate [searchPathSeparator] $ concat
156156
[ [toFilePathNoTrailingSep localdb | locals]
157157
, [toFilePathNoTrailingSep deps]
158158
, [toFilePathNoTrailingSep db | db <- reverse extras]

0 commit comments

Comments
 (0)