Skip to content

Commit f108389

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 d4a24d2 commit f108389

File tree

15 files changed

+537
-53
lines changed

15 files changed

+537
-53
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

@@ -174,9 +175,24 @@ docProjectConfigFiles ps = vcat
174175
-- | A message for a cyclical import, a "cyclical import of".
175176
cyclicalImportMsg :: ProjectConfigPath -> Doc
176177
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
178+
seenImportMsg (text "cyclical import of" <+> text duplicate <> semi) duplicate path []
179+
180+
-- | A message for a duplicate import, a "duplicate import of". If a check for
181+
-- cyclical imports has already been made then this would report a duplicate
182+
-- import by two different paths.
183+
duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
184+
duplicateImportMsg intro = seenImportMsg intro
185+
186+
seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
187+
seenImportMsg intro duplicate path seenImportsBy =
177188
vcat
178-
[ text "cyclical import of" <+> text duplicate <> semi
189+
[ intro
179190
, nest 2 (docProjectConfigPath path)
191+
, nest 2 $
192+
vcat
193+
[ docProjectConfigPath dib
194+
| (_, dib) <- filter ((duplicate ==) . fst) seenImportsBy
195+
]
180196
]
181197

182198
-- | 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 RecordWildCards #-}
76
{-# LANGUAGE ScopedTypeVariables #-}
@@ -35,6 +34,7 @@ module Distribution.Client.ProjectConfig.Legacy
3534
) where
3635

3736
import Data.Coerce (coerce)
37+
import Data.IORef
3838
import Distribution.Client.Compat.Prelude
3939

4040
import Distribution.Types.Flag (FlagName, parsecFlagAssignment)
@@ -142,7 +142,8 @@ import Distribution.Types.CondTree
142142
)
143143
import Distribution.Types.SourceRepo (RepoType)
144144
import Distribution.Utils.NubList
145-
( fromNubList
145+
( NubList
146+
, fromNubList
146147
, overNubList
147148
, toNubList
148149
)
@@ -194,7 +195,7 @@ import Distribution.Utils.Path hiding
194195
)
195196

196197
import qualified Data.ByteString.Char8 as BS
197-
import Data.Functor ((<&>))
198+
import Data.List (sortOn)
198199
import qualified Data.Map as Map
199200
import qualified Data.Set as Set
200201
import Network.URI (URI (..), nullURIAuth, parseURI)
@@ -203,9 +204,12 @@ import System.FilePath (isAbsolute, isPathSeparator, makeValid, splitFileName, (
203204
import Text.PrettyPrint
204205
( Doc
205206
, render
207+
, semi
208+
, text
209+
, vcat
206210
, ($+$)
207211
)
208-
import qualified Text.PrettyPrint as Disp
212+
import qualified Text.PrettyPrint as Disp (empty, int, render, text)
209213

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

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

287-
-- Once we canonicalize the import path, we can check for cyclical imports
315+
-- Once we canonicalize the import path, we can check for cyclical and duplicate imports
288316
normSource <- canonicalizeConfigPath projectDir source
289-
normLocPath <- canonicalizeConfigPath projectDir importLocPath
317+
normLocPath@(ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath
318+
seenImportsBy@(fmap fst -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [(uniqueImport, normLocPath)] <> ibs, ibs))
290319
debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath)
320+
debug verbosity "\nseen unique paths\n================="
321+
mapM_ (debug verbosity) seenImports
322+
debug verbosity "\n"
291323

292324
if isCyclicConfigPath normLocPath
293325
then pure . projectParseFail Nothing (Just normSource) $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
@@ -296,8 +328,10 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project
296328
(isUntrimmedUriConfigPath importLocPath)
297329
(noticeDoc verbosity $ untrimmedUriImportMsg (Disp.text "Warning:") importLocPath)
298330
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
299-
res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
300-
rest <- go [] xs
331+
let uniqueFields = if uniqueImport `elem` seenImports then [] else xs
332+
atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes uniqueImport normLocPath seenImportsBy] dm, ())
333+
res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
334+
rest <- go [] uniqueFields
301335
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
302336
(ParseUtils.Section l "if" p xs') -> do
303337
normSource <- canonicalizeConfigPath projectDir source

0 commit comments

Comments
 (0)