Skip to content

Commit be3dea6

Browse files
committed
Render duplicate imports
1 parent 9204513 commit be3dea6

File tree

4 files changed

+142
-149
lines changed

4 files changed

+142
-149
lines changed

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

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -174,18 +174,19 @@ docProjectConfigFiles ps = vcat
174174

175175
-- | A message for a cyclical import, a "cyclical import of".
176176
cyclicalImportMsg :: ProjectConfigPath -> Doc
177-
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) = seenImportMsg "cyclical" duplicate path []
177+
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
178+
seenImportMsg (text "cyclical import of" <+> text duplicate <> semi) duplicate path []
178179

179180
-- | A message for a duplicate import, a "duplicate import of". If a check for
180181
-- cyclical imports has already been made then this would report a duplicate
181182
-- import by two different paths.
182-
duplicateImportMsg :: FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
183-
duplicateImportMsg = seenImportMsg "duplicate"
183+
duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
184+
duplicateImportMsg intro = seenImportMsg intro
184185

185-
seenImportMsg :: String -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
186-
seenImportMsg seen duplicate path seenImportsBy =
186+
seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
187+
seenImportMsg intro duplicate path seenImportsBy =
187188
vcat
188-
[ text seen <+> text "import of" <+> text duplicate <> semi
189+
[ intro
189190
, nest 2 (docProjectConfigPath path)
190191
, nest 2 $
191192
vcat

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

Lines changed: 34 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -208,8 +208,12 @@ import Text.PrettyPrint
208208
( Doc
209209
, render
210210
, ($+$)
211+
, vcat
212+
, text
213+
, semi
211214
)
212-
import qualified Text.PrettyPrint as Disp
215+
import qualified Text.PrettyPrint as Disp (empty, int, text, render)
216+
import Data.List (sortOn)
213217

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

273291
parseProjectSkeleton
274292
:: FilePath
275293
-> HttpTransport
276294
-> Verbosity
277295
-> IORef (NubList (FilePath, ProjectConfigPath))
278296
-- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
297+
-> IORef DupesMap
298+
-- ^ The duplicates seen so far, used to defer reporting on duplicates
279299
-> FilePath
280300
-- ^ The directory of the project configuration, typically the directory of cabal.project
281301
-> ProjectConfigPath
282302
-- ^ The path of the file being parsed, either the root or an import
283303
-> ProjectConfigToParse
284304
-- ^ The contents of the file to parse
285305
-> IO (ProjectParseResult ProjectConfigSkeleton)
286-
parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir source (ProjectConfigToParse bs) =
306+
parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir source (ProjectConfigToParse bs) =
287307
(sanityWalkPCS False =<<) <$> liftPR source (go []) (ParseUtils.readFields bs)
288308
where
289309
go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ProjectParseResult ProjectConfigSkeleton)
@@ -310,13 +330,9 @@ parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir sourc
310330
(isUntrimmedUriConfigPath importLocPath)
311331
(noticeDoc verbosity $ untrimmedUriImportMsg (Disp.text "Warning:") importLocPath)
312332
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
313-
res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
314-
uniqueFields <-
315-
if uniqueImport `elem` seenImports
316-
then do
317-
noticeDoc verbosity $ duplicateImportMsg uniqueImport normLocPath seenImportsBy
318-
return []
319-
else return xs
333+
let uniqueFields = if uniqueImport `elem` seenImports then [] else xs
334+
atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes uniqueImport normLocPath seenImportsBy] dm, ())
335+
res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
320336
rest <- go [] uniqueFields
321337
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
322338
(ParseUtils.Section l "if" p xs') -> do

cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out

Lines changed: 99 additions & 123 deletions
Original file line numberDiff line numberDiff line change
@@ -254,130 +254,106 @@ Could not resolve dependencies:
254254
(constraint from oops-0.project requires ==1.4.3.0)
255255
[__1] fail (backjumping, conflict set: hashable, oops)
256256
After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), oops (2)
257-
# checking if we detect when the same config is imported via many different paths (we don't)
257+
# checking that we detect when the same config is imported via many different paths
258258
# cabal v2-build
259-
Configuration is affected by the following files:
260-
- yops-0.project
261-
- yops-2.config
262-
imported by: yops/yops-1.config
263-
imported by: yops-0.project
264-
- yops-4.config
265-
imported by: yops/yops-3.config
266-
imported by: yops-0.project
267-
- yops-4.config
268-
imported by: yops/yops-3.config
269-
imported by: yops-2.config
270-
imported by: yops/yops-1.config
271-
imported by: yops-0.project
272-
- yops-6.config
273-
imported by: yops/yops-5.config
274-
imported by: yops-0.project
275-
- yops-6.config
276-
imported by: yops/yops-5.config
277-
imported by: yops-4.config
278-
imported by: yops/yops-3.config
279-
imported by: yops-0.project
280-
- yops-6.config
281-
imported by: yops/yops-5.config
282-
imported by: yops-4.config
283-
imported by: yops/yops-3.config
284-
imported by: yops-2.config
285-
imported by: yops/yops-1.config
286-
imported by: yops-0.project
287-
- yops-8.config
288-
imported by: yops/yops-7.config
289-
imported by: yops-0.project
290-
- yops-8.config
291-
imported by: yops/yops-7.config
292-
imported by: yops-6.config
293-
imported by: yops/yops-5.config
294-
imported by: yops-0.project
295-
- yops-8.config
296-
imported by: yops/yops-7.config
297-
imported by: yops-6.config
298-
imported by: yops/yops-5.config
299-
imported by: yops-4.config
300-
imported by: yops/yops-3.config
301-
imported by: yops-0.project
302-
- yops-8.config
303-
imported by: yops/yops-7.config
304-
imported by: yops-6.config
305-
imported by: yops/yops-5.config
306-
imported by: yops-4.config
307-
imported by: yops/yops-3.config
308-
imported by: yops-2.config
309-
imported by: yops/yops-1.config
310-
imported by: yops-0.project
311-
- yops/yops-1.config
312-
imported by: yops-0.project
313-
- yops/yops-3.config
314-
imported by: yops-0.project
315-
- yops/yops-3.config
316-
imported by: yops-2.config
317-
imported by: yops/yops-1.config
318-
imported by: yops-0.project
319-
- yops/yops-5.config
320-
imported by: yops-0.project
321-
- yops/yops-5.config
322-
imported by: yops-4.config
323-
imported by: yops/yops-3.config
324-
imported by: yops-0.project
325-
- yops/yops-5.config
326-
imported by: yops-4.config
327-
imported by: yops/yops-3.config
328-
imported by: yops-2.config
329-
imported by: yops/yops-1.config
330-
imported by: yops-0.project
331-
- yops/yops-7.config
332-
imported by: yops-0.project
333-
- yops/yops-7.config
334-
imported by: yops-6.config
335-
imported by: yops/yops-5.config
336-
imported by: yops-0.project
337-
- yops/yops-7.config
338-
imported by: yops-6.config
339-
imported by: yops/yops-5.config
340-
imported by: yops-4.config
341-
imported by: yops/yops-3.config
342-
imported by: yops-0.project
343-
- yops/yops-7.config
344-
imported by: yops-6.config
345-
imported by: yops/yops-5.config
346-
imported by: yops-4.config
347-
imported by: yops/yops-3.config
348-
imported by: yops-2.config
349-
imported by: yops/yops-1.config
350-
imported by: yops-0.project
351-
- yops/yops-9.config
352-
imported by: yops-0.project
353-
- yops/yops-9.config
354-
imported by: yops-8.config
355-
imported by: yops/yops-7.config
356-
imported by: yops-0.project
357-
- yops/yops-9.config
358-
imported by: yops-8.config
359-
imported by: yops/yops-7.config
360-
imported by: yops-6.config
361-
imported by: yops/yops-5.config
362-
imported by: yops-0.project
363-
- yops/yops-9.config
364-
imported by: yops-8.config
365-
imported by: yops/yops-7.config
366-
imported by: yops-6.config
367-
imported by: yops/yops-5.config
368-
imported by: yops-4.config
369-
imported by: yops/yops-3.config
370-
imported by: yops-0.project
371-
- yops/yops-9.config
372-
imported by: yops-8.config
373-
imported by: yops/yops-7.config
374-
imported by: yops-6.config
375-
imported by: yops/yops-5.config
376-
imported by: yops-4.config
377-
imported by: yops/yops-3.config
378-
imported by: yops-2.config
379-
imported by: yops/yops-1.config
380-
imported by: yops-0.project
259+
Warning: 2 imports of
260+
yops-4.config;
261+
yops-4.config
262+
imported by: yops/yops-3.config
263+
imported by: yops-0.project
264+
yops-4.config
265+
imported by: yops/yops-3.config
266+
imported by: yops-2.config
267+
imported by: yops/yops-1.config
268+
imported by: yops-0.project
269+
Warning: 2 imports of
270+
yops-6.config;
271+
yops-6.config
272+
imported by: yops/yops-5.config
273+
imported by: yops-4.config
274+
imported by: yops/yops-3.config
275+
imported by: yops-0.project
276+
yops-6.config
277+
imported by: yops/yops-5.config
278+
imported by: yops-4.config
279+
imported by: yops/yops-3.config
280+
imported by: yops-2.config
281+
imported by: yops/yops-1.config
282+
imported by: yops-0.project
283+
Warning: 2 imports of
284+
yops-8.config;
285+
yops-8.config
286+
imported by: yops/yops-7.config
287+
imported by: yops-6.config
288+
imported by: yops/yops-5.config
289+
imported by: yops-4.config
290+
imported by: yops/yops-3.config
291+
imported by: yops-0.project
292+
yops-8.config
293+
imported by: yops/yops-7.config
294+
imported by: yops-6.config
295+
imported by: yops/yops-5.config
296+
imported by: yops-4.config
297+
imported by: yops/yops-3.config
298+
imported by: yops-2.config
299+
imported by: yops/yops-1.config
300+
imported by: yops-0.project
301+
Warning: 2 imports of
302+
yops/yops-3.config;
303+
yops/yops-3.config
304+
imported by: yops-0.project
305+
yops/yops-3.config
306+
imported by: yops-2.config
307+
imported by: yops/yops-1.config
308+
imported by: yops-0.project
309+
Warning: 2 imports of
310+
yops/yops-5.config;
311+
yops/yops-5.config
312+
imported by: yops-4.config
313+
imported by: yops/yops-3.config
314+
imported by: yops-0.project
315+
yops/yops-5.config
316+
imported by: yops-4.config
317+
imported by: yops/yops-3.config
318+
imported by: yops-2.config
319+
imported by: yops/yops-1.config
320+
imported by: yops-0.project
321+
Warning: 2 imports of
322+
yops/yops-7.config;
323+
yops/yops-7.config
324+
imported by: yops-6.config
325+
imported by: yops/yops-5.config
326+
imported by: yops-4.config
327+
imported by: yops/yops-3.config
328+
imported by: yops-0.project
329+
yops/yops-7.config
330+
imported by: yops-6.config
331+
imported by: yops/yops-5.config
332+
imported by: yops-4.config
333+
imported by: yops/yops-3.config
334+
imported by: yops-2.config
335+
imported by: yops/yops-1.config
336+
imported by: yops-0.project
337+
Warning: 2 imports of
338+
yops/yops-9.config;
339+
yops/yops-9.config
340+
imported by: yops-8.config
341+
imported by: yops/yops-7.config
342+
imported by: yops-6.config
343+
imported by: yops/yops-5.config
344+
imported by: yops-4.config
345+
imported by: yops/yops-3.config
346+
imported by: yops-0.project
347+
yops/yops-9.config
348+
imported by: yops-8.config
349+
imported by: yops/yops-7.config
350+
imported by: yops-6.config
351+
imported by: yops/yops-5.config
352+
imported by: yops-4.config
353+
imported by: yops/yops-3.config
354+
imported by: yops-2.config
355+
imported by: yops/yops-1.config
356+
imported by: yops-0.project
381357
Up to date
382358
# checking bad conditional
383359
# cabal v2-build

cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -193,8 +193,8 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do
193193
-- +-- yops/yops-9.config (no further imports)
194194
-- +-- yops/yops-9.config (no further imports)
195195
log "checking that we detect when the same config is imported via many different paths"
196-
yopping <- fails $ cabal' "v2-build" [ "--project-file=yops-0.project" ]
197-
assertOutputContains "duplicate import of yops/yops-3.config" yopping
196+
yopping <- cabal' "v2-build" [ "--project-file=yops-0.project" ]
197+
assertOutputContains "Warning: 2 imports" yopping
198198

199199
log "checking bad conditional"
200200
badIf <- fails $ cabal' "v2-build" [ "--project-file=bad-conditional.project" ]

0 commit comments

Comments
 (0)