Skip to content

Commit a727dc4

Browse files
committed
Warn on duplicate non-cyclical project imports
- Add Y-forking import test - A test for detecting when the same config is imported via many different paths - Error on duplicate imports - Do the filtering in duplicateImportMsg - Use duplicateImportMsg for cycles too - Add haddocks to IORef parameter - Add changelog entry - Use ordNub instead of nub - Use NubList - Share implement of duplicate and cyclical messages - Update expectation for non-cyclical duplicate import - Only show a warning - Add woops project with a time cost - Use noticeDoc instead of warn - Render duplicate imports - Add Ord instance for Dupes, sort on dupesNormLocPath - Fixups after rebase - Satisfy hlint - Remove -XMultiWayIf - Remove mention of yops from the changelog - Satisfy fix-whitespace - Test with a time cost of duplicate imports
1 parent 6d6fc4c commit a727dc4

File tree

15 files changed

+538
-23
lines changed

15 files changed

+538
-23
lines changed

cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs

Lines changed: 17 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Distribution.Solver.Types.ProjectConfigPath
1414
, docProjectConfigPath
1515
, docProjectConfigFiles
1616
, cyclicalImportMsg
17+
, duplicateImportMsg
1718
, untrimmedUriImportMsg
1819
, docProjectConfigPathFailReason
1920
, quoteUntrimmed
@@ -178,9 +179,24 @@ docProjectConfigFiles ps = vcat
178179
-- | A message for a cyclical import, a "cyclical import of".
179180
cyclicalImportMsg :: ProjectConfigPath -> Doc
180181
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
182+
seenImportMsg (text "cyclical import of" <+> text duplicate <> semi) duplicate path []
183+
184+
-- | A message for a duplicate import, a "duplicate import of". If a check for
185+
-- cyclical imports has already been made then this would report a duplicate
186+
-- import by two different paths.
187+
duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
188+
duplicateImportMsg intro = seenImportMsg intro
189+
190+
seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
191+
seenImportMsg intro duplicate path seenImportsBy =
181192
vcat
182-
[ text "cyclical import of" <+> text duplicate <> semi
193+
[ intro
183194
, nest 2 (docProjectConfigPath path)
195+
, nest 2 $
196+
vcat
197+
[ docProjectConfigPath dib
198+
| (_, dib) <- filter ((duplicate ==) . fst) seenImportsBy
199+
]
184200
]
185201

186202
-- | A message for an import that has leading or trailing spaces.

cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs

Lines changed: 51 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE ConstraintKinds #-}
22
{-# LANGUAGE DataKinds #-}
33
{-# LANGUAGE DeriveGeneric #-}
4-
{-# LANGUAGE LambdaCase #-}
54
{-# LANGUAGE NamedFieldPuns #-}
65
{-# LANGUAGE PatternSynonyms #-}
76
{-# LANGUAGE RecordWildCards #-}
@@ -36,6 +35,7 @@ module Distribution.Client.ProjectConfig.Legacy
3635
) where
3736

3837
import Data.Coerce (coerce)
38+
import Data.IORef
3939
import Distribution.Client.Compat.Prelude
4040

4141
import Distribution.Types.Flag (FlagName, parsecFlagAssignment)
@@ -145,7 +145,8 @@ import Distribution.Types.CondTree
145145
)
146146
import Distribution.Types.SourceRepo (RepoType)
147147
import Distribution.Utils.NubList
148-
( fromNubList
148+
( NubList
149+
, fromNubList
149150
, overNubList
150151
, toNubList
151152
)
@@ -197,7 +198,7 @@ import Distribution.Utils.Path hiding
197198
)
198199

199200
import qualified Data.ByteString.Char8 as BS
200-
import Data.Functor ((<&>))
201+
import Data.List (sortOn)
201202
import qualified Data.Map as Map
202203
import qualified Data.Set as Set
203204
import Network.URI (URI (..), nullURIAuth, parseURI)
@@ -206,9 +207,12 @@ import System.FilePath (isAbsolute, isPathSeparator, makeValid, splitFileName, (
206207
import Text.PrettyPrint
207208
( Doc
208209
, render
210+
, semi
211+
, text
212+
, vcat
209213
, ($+$)
210214
)
211-
import qualified Text.PrettyPrint as Disp
215+
import qualified Text.PrettyPrint as Disp (empty, int, render, text)
212216

213217
------------------------------------------------------------------
214218
-- Handle extended project config files with conditionals and imports.
@@ -259,38 +263,66 @@ parseProject
259263
-> ProjectConfigToParse
260264
-- ^ The contents of the file to parse
261265
-> IO (ProjectParseResult ProjectConfigSkeleton)
262-
parseProject rootPath cacheDir httpTransport verbosity configToParse =
263-
do
264-
let (dir, projectFileName) = splitFileName rootPath
265-
projectDir <- makeAbsolute dir
266-
projectPath <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
267-
parseProjectSkeleton cacheDir httpTransport verbosity projectDir projectPath configToParse
268-
-- NOTE: Reverse the warnings so they are in line number order.
269-
<&> \case ProjectParseOk ws x -> ProjectParseOk (reverse ws) x; x -> x
266+
parseProject rootPath cacheDir httpTransport verbosity configToParse = do
267+
let (dir, projectFileName) = splitFileName rootPath
268+
projectDir <- makeAbsolute dir
269+
projectPath@(ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
270+
importsBy <- newIORef $ toNubList [(canonicalRoot, projectPath)]
271+
dupesMap <- newIORef mempty
272+
result <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir projectPath configToParse
273+
dupes <- Map.filter ((> 1) . length) <$> readIORef dupesMap
274+
unless (Map.null dupes) (noticeDoc verbosity $ vcat (dupesMsg <$> Map.toList dupes))
275+
return result
276+
277+
data Dupes = Dupes
278+
{ dupesUniqueImport :: FilePath
279+
, dupesNormLocPath :: ProjectConfigPath
280+
, dupesSeenImportsBy :: [(FilePath, ProjectConfigPath)]
281+
}
282+
deriving (Eq)
283+
284+
instance Ord Dupes where
285+
compare = compare `on` length . dupesSeenImportsBy
286+
287+
type DupesMap = Map FilePath [Dupes]
288+
289+
dupesMsg :: (FilePath, [Dupes]) -> Doc
290+
dupesMsg (duplicate, ds@(take 1 . sortOn dupesNormLocPath -> dupes)) =
291+
vcat $
292+
((text "Warning:" <+> Disp.int (length ds) <+> text "imports of" <+> text duplicate) <> semi)
293+
: ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesUniqueImport dupesNormLocPath dupesSeenImportsBy) <$> dupes)
270294

271295
parseProjectSkeleton
272296
:: FilePath
273297
-> HttpTransport
274298
-> Verbosity
299+
-> IORef (NubList (FilePath, ProjectConfigPath))
300+
-- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
301+
-> IORef DupesMap
302+
-- ^ The duplicates seen so far, used to defer reporting on duplicates
275303
-> FilePath
276304
-- ^ The directory of the project configuration, typically the directory of cabal.project
277305
-> ProjectConfigPath
278306
-- ^ The path of the file being parsed, either the root or an import
279307
-> ProjectConfigToParse
280308
-- ^ The contents of the file to parse
281309
-> IO (ProjectParseResult ProjectConfigSkeleton)
282-
parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
310+
parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir source (ProjectConfigToParse bs) =
283311
(sanityWalkPCS False =<<) <$> liftPR source (go []) (ParseUtils.readFields bs)
284312
where
285313
go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ProjectParseResult ProjectConfigSkeleton)
286314
go acc (x : xs) = case x of
287315
(ParseUtils.F _ "import" importLoc) -> do
288316
let importLocPath = importLoc `consProjectConfigPath` source
289317

290-
-- Once we canonicalize the import path, we can check for cyclical imports
318+
-- Once we canonicalize the import path, we can check for cyclical and duplicate imports
291319
normSource <- canonicalizeConfigPath projectDir source
292-
normLocPath <- canonicalizeConfigPath projectDir importLocPath
320+
normLocPath@(ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath
321+
seenImportsBy@(fmap fst -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [(uniqueImport, normLocPath)] <> ibs, ibs))
293322
debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath)
323+
debug verbosity "\nseen unique paths\n================="
324+
mapM_ (debug verbosity) seenImports
325+
debug verbosity "\n"
294326

295327
if isCyclicConfigPath normLocPath
296328
then pure . projectParseFail Nothing (Just normSource) $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
@@ -299,8 +331,10 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project
299331
(isUntrimmedUriConfigPath importLocPath)
300332
(noticeDoc verbosity $ untrimmedUriImportMsg (Disp.text "Warning:") importLocPath)
301333
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
302-
res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
303-
rest <- go [] xs
334+
let uniqueFields = if uniqueImport `elem` seenImports then [] else xs
335+
atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes uniqueImport normLocPath seenImportsBy] dm, ())
336+
res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
337+
rest <- go [] uniqueFields
304338
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
305339
(ParseUtils.Section l "if" p xs') -> do
306340
normSource <- canonicalizeConfigPath projectDir source

0 commit comments

Comments
 (0)