Skip to content

Commit 3d032f3

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 - Fewer imports from PrettyPrint qualified as Disp - Add data ProjectImport replacing tuples - Combine fields as ProjectImport - Rename field to dupesImports - Add haddocks to Dupes fields - Mark test as flaky - Any test accessing stackage seems susceptible - Move unique duplicates to own test - Use legacy parser for path duplicates test - Add foo.cabal package so that packages exist - Satisfy fix-whitespace - Use local version of lts-21.25 - Remove repo - Use </> for expected paths - Note that this change gives a warning.
1 parent 59c80b7 commit 3d032f3

File tree

31 files changed

+3488
-78
lines changed

31 files changed

+3488
-78
lines changed

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

Lines changed: 30 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
11
{-# LANGUAGE DeriveGeneric #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
23
{-# LANGUAGE ViewPatterns #-}
34

45
module Distribution.Solver.Types.ProjectConfigPath
56
(
67
-- * Project Config Path Manipulation
7-
ProjectConfigPath(..)
8+
ProjectImport(..)
9+
, ProjectConfigPath(..)
810
, projectConfigPathRoot
911
, nullProjectConfigPath
1012
, consProjectConfigPath
@@ -16,6 +18,7 @@ module Distribution.Solver.Types.ProjectConfigPath
1618
, docProjectImportedBy
1719
, docProjectConfigFiles
1820
, cyclicalImportMsg
21+
, duplicateImportMsg
1922
, untrimmedUriImportMsg
2023
, docProjectConfigPathFailReason
2124
, quoteUntrimmed
@@ -47,6 +50,13 @@ import Text.PrettyPrint
4750
import Distribution.Simple.Utils (ordNub)
4851
import Distribution.System (OS(Windows), buildOS)
4952

53+
data ProjectImport =
54+
ProjectImport
55+
{ importOf :: FilePath
56+
, importBy :: ProjectConfigPath
57+
}
58+
deriving (Eq, Ord)
59+
5060
-- | Path to a configuration file, either a singleton project root, or a longer
5161
-- list representing a path to an import. The path is a non-empty list that we
5262
-- build up by prepending relative imports with @consProjectConfigPath@.
@@ -187,9 +197,27 @@ docProjectConfigFiles ps = vcat
187197
-- | A message for a cyclical import, a "cyclical import of".
188198
cyclicalImportMsg :: ProjectConfigPath -> Doc
189199
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
200+
seenImportMsg
201+
(text "cyclical import of" <+> text duplicate <> semi)
202+
(ProjectImport duplicate path)
203+
[]
204+
205+
-- | A message for a duplicate import, a "duplicate import of". If a check for
206+
-- cyclical imports has already been made then this would report a duplicate
207+
-- import by two different paths.
208+
duplicateImportMsg :: Doc -> ProjectImport -> [ProjectImport] -> Doc
209+
duplicateImportMsg intro = seenImportMsg intro
210+
211+
seenImportMsg :: Doc -> ProjectImport -> [ProjectImport] -> Doc
212+
seenImportMsg intro ProjectImport{importOf = duplicate, importBy = path} seenImports =
190213
vcat
191-
[ text "cyclical import of" <+> text duplicate <> semi
214+
[ intro
192215
, nest 2 (docProjectConfigPath path)
216+
, nest 2 $
217+
vcat
218+
[ docProjectConfigPath importBy
219+
| ProjectImport{importBy} <- filter ((duplicate ==) . importOf) seenImports
220+
]
193221
]
194222

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

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

Lines changed: 67 additions & 39 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,18 +198,14 @@ 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)
204205
import System.Directory (createDirectoryIfMissing, makeAbsolute)
205206
import System.FilePath (isAbsolute, isPathSeparator, makeValid, splitFileName, (</>))
206-
import Text.PrettyPrint
207-
( Doc
208-
, render
209-
, ($+$)
210-
)
211-
import qualified Text.PrettyPrint as Disp
207+
import Text.PrettyPrint (Doc, int, render, semi, text, vcat, ($+$))
208+
import qualified Text.PrettyPrint as Disp (empty)
212209

213210
------------------------------------------------------------------
214211
-- Handle extended project config files with conditionals and imports.
@@ -259,48 +256,79 @@ parseProject
259256
-> ProjectConfigToParse
260257
-- ^ The contents of the file to parse
261258
-> 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
259+
parseProject rootPath cacheDir httpTransport verbosity configToParse = do
260+
let (dir, projectFileName) = splitFileName rootPath
261+
projectDir <- makeAbsolute dir
262+
projectPath@(ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
263+
importsBy <- newIORef $ toNubList [ProjectImport canonicalRoot projectPath]
264+
dupesMap <- newIORef mempty
265+
result <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir projectPath configToParse
266+
dupes <- Map.filter ((> 1) . length) <$> readIORef dupesMap
267+
unless (Map.null dupes) (noticeDoc verbosity $ vcat (dupesMsg <$> Map.toList dupes))
268+
return result
269+
270+
data Dupes = Dupes
271+
{ dupesImport :: ProjectImport
272+
-- ^ The import that we're checking for duplicates.
273+
, dupesImports :: [ProjectImport]
274+
-- ^ All the imports of this file.
275+
}
276+
deriving (Eq)
277+
278+
instance Ord Dupes where
279+
compare = compare `on` length . dupesImports
280+
281+
type DupesMap = Map FilePath [Dupes]
282+
283+
dupesMsg :: (FilePath, [Dupes]) -> Doc
284+
dupesMsg (duplicate, ds@(take 1 . sortOn (importBy . dupesImport) -> dupes)) =
285+
vcat $
286+
((text "Warning:" <+> int (length ds) <+> text "imports of" <+> text duplicate) <> semi)
287+
: ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesImport dupesImports) <$> dupes)
270288

271289
parseProjectSkeleton
272290
:: FilePath
273291
-> HttpTransport
274292
-> Verbosity
293+
-> IORef (NubList ProjectImport)
294+
-- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
295+
-> IORef DupesMap
296+
-- ^ The duplicates seen so far, used to defer reporting on duplicates
275297
-> FilePath
276298
-- ^ The directory of the project configuration, typically the directory of cabal.project
277299
-> ProjectConfigPath
278300
-- ^ The path of the file being parsed, either the root or an import
279301
-> ProjectConfigToParse
280302
-- ^ The contents of the file to parse
281303
-> IO (ProjectParseResult ProjectConfigSkeleton)
282-
parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
304+
parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir source (ProjectConfigToParse bs) =
283305
(sanityWalkPCS False =<<) <$> liftPR source (go []) (ParseUtils.readFields bs)
284306
where
285307
go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ProjectParseResult ProjectConfigSkeleton)
286308
go acc (x : xs) = case x of
287309
(ParseUtils.F _ "import" importLoc) -> do
288310
let importLocPath = importLoc `consProjectConfigPath` source
289311

290-
-- Once we canonicalize the import path, we can check for cyclical imports
312+
-- Once we canonicalize the import path, we can check for cyclical and duplicate imports
291313
normSource <- canonicalizeConfigPath projectDir source
292-
normLocPath <- canonicalizeConfigPath projectDir importLocPath
314+
normLocPath@(ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath
315+
seenImportsBy@(fmap importOf -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [ProjectImport uniqueImport normLocPath] <> ibs, ibs))
293316
debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath)
317+
debug verbosity "\nseen unique paths\n================="
318+
mapM_ (debug verbosity) seenImports
319+
debug verbosity "\n"
294320

295321
if isCyclicConfigPath normLocPath
296322
then pure . projectParseFail Nothing (Just normSource) $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
297323
else do
298324
when
299325
(isUntrimmedUriConfigPath importLocPath)
300-
(noticeDoc verbosity $ untrimmedUriImportMsg (Disp.text "Warning:") importLocPath)
326+
(noticeDoc verbosity $ untrimmedUriImportMsg (text "Warning:") importLocPath)
301327
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
328+
let uniqueFields = if uniqueImport `elem` seenImports then [] else xs
329+
atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes (ProjectImport uniqueImport normLocPath) seenImportsBy] dm, ())
330+
res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
331+
rest <- go [] uniqueFields
304332
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
305333
(ParseUtils.Section l "if" p xs') -> do
306334
normSource <- canonicalizeConfigPath projectDir source
@@ -1295,13 +1323,13 @@ parseLegacyProjectConfig rootConfig bs =
12951323

12961324
showLegacyProjectConfig :: LegacyProjectConfig -> String
12971325
showLegacyProjectConfig config =
1298-
Disp.render $
1326+
render $
12991327
showConfig
13001328
(legacyProjectConfigFieldDescrs constraintSrc)
13011329
legacyPackageConfigSectionDescrs
13021330
legacyPackageConfigFGSectionDescrs
13031331
config
1304-
$+$ Disp.text ""
1332+
$+$ text ""
13051333
where
13061334
-- Note: ConstraintSource is unused when pretty-printing. We fake
13071335
-- it here to avoid having to pass it on call-sites. It's not great
@@ -1312,13 +1340,13 @@ legacyProjectConfigFieldDescrs :: ConstraintSource -> [FieldDescr LegacyProjectC
13121340
legacyProjectConfigFieldDescrs constraintSrc =
13131341
[ newLineListField
13141342
"packages"
1315-
(Disp.text . renderPackageLocationToken)
1343+
(text . renderPackageLocationToken)
13161344
parsePackageLocationTokenQ
13171345
legacyPackages
13181346
(\v flags -> flags{legacyPackages = v})
13191347
, newLineListField
13201348
"optional-packages"
1321-
(Disp.text . renderPackageLocationToken)
1349+
(text . renderPackageLocationToken)
13221350
parsePackageLocationTokenQ
13231351
legacyPackagesOptional
13241352
(\v flags -> flags{legacyPackagesOptional = v})
@@ -1429,7 +1457,7 @@ legacySharedConfigFieldDescrs constraintSrc =
14291457
. addFields
14301458
[ commaNewLineListFieldParsec
14311459
"package-dbs"
1432-
(Disp.text . showPackageDb)
1460+
(text . showPackageDb)
14331461
(fmap readPackageDb parsecToken)
14341462
configPackageDBs
14351463
(\v conf -> conf{configPackageDBs = v})
@@ -1722,8 +1750,8 @@ legacyPackageConfigFieldDescrs =
17221750
in FieldDescr
17231751
name
17241752
( \f -> case f of
1725-
Flag NoDumpBuildInfo -> Disp.text "False"
1726-
Flag DumpBuildInfo -> Disp.text "True"
1753+
Flag NoDumpBuildInfo -> text "False"
1754+
Flag DumpBuildInfo -> text "True"
17271755
_ -> Disp.empty
17281756
)
17291757
( \line str _ -> case () of
@@ -1750,9 +1778,9 @@ legacyPackageConfigFieldDescrs =
17501778
in FieldDescr
17511779
name
17521780
( \f -> case f of
1753-
Flag NoOptimisation -> Disp.text "False"
1754-
Flag NormalOptimisation -> Disp.text "True"
1755-
Flag MaximumOptimisation -> Disp.text "2"
1781+
Flag NoOptimisation -> text "False"
1782+
Flag NormalOptimisation -> text "True"
1783+
Flag MaximumOptimisation -> text "2"
17561784
_ -> Disp.empty
17571785
)
17581786
( \line str _ -> case () of
@@ -1775,10 +1803,10 @@ legacyPackageConfigFieldDescrs =
17751803
in FieldDescr
17761804
name
17771805
( \f -> case f of
1778-
Flag NoDebugInfo -> Disp.text "False"
1779-
Flag MinimalDebugInfo -> Disp.text "1"
1780-
Flag NormalDebugInfo -> Disp.text "True"
1781-
Flag MaximalDebugInfo -> Disp.text "3"
1806+
Flag NoDebugInfo -> text "False"
1807+
Flag MinimalDebugInfo -> text "1"
1808+
Flag NormalDebugInfo -> text "True"
1809+
Flag MaximalDebugInfo -> text "3"
17821810
_ -> Disp.empty
17831811
)
17841812
( \line str _ -> case () of
@@ -2103,6 +2131,6 @@ monoidFieldParsec name showF readF get' set =
21032131
-- otherwise are special syntax.
21042132
showTokenQ :: String -> Doc
21052133
showTokenQ "" = Disp.empty
2106-
showTokenQ x@('-' : '-' : _) = Disp.text (show x)
2107-
showTokenQ x@('.' : []) = Disp.text (show x)
2134+
showTokenQ x@('-' : '-' : _) = text (show x)
2135+
showTokenQ x@('.' : []) = text (show x)
21082136
showTokenQ x = showToken x

cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -194,9 +194,6 @@ Could not resolve dependencies:
194194
(constraint from oops-0.project requires ==1.4.3.0)
195195
[__1] fail (backjumping, conflict set: hashable, oops)
196196
After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), oops (2)
197-
# checking if we detect when the same config is imported via many different paths (we don't)
198-
# cabal v2-build
199-
Up to date
200197
# checking bad conditional
201198
# cabal v2-build
202199
Error: [Cabal-7167]

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

Lines changed: 0 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -133,39 +133,6 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do
133133
readFileVerbatim "oops.expect.txt"
134134
>>= flip (assertOn isInfixOf multilineNeedleHaystack) oopsing . normalizePathSeparators
135135

136-
-- The project is named yops as it is like hops but with y's for forks.
137-
-- +-- yops-0.project
138-
-- +-- yops/yops-1.config
139-
-- +-- yops-2.config
140-
-- +-- yops/yops-3.config
141-
-- +-- yops-4.config
142-
-- +-- yops/yops-5.config
143-
-- +-- yops-6.config
144-
-- +-- yops/yops-7.config
145-
-- +-- yops-8.config
146-
-- +-- yops/yops-9.config (no further imports)
147-
-- +-- yops/yops-3.config
148-
-- +-- yops-4.config
149-
-- +-- yops/yops-5.config
150-
-- +-- yops-6.config
151-
-- +-- yops/yops-7.config
152-
-- +-- yops-8.config
153-
-- +-- yops/yops-9.config (no further imports)
154-
-- +-- yops/yops-5.config
155-
-- +-- yops-6.config
156-
-- +-- yops/yops-7.config
157-
-- +-- yops-8.config
158-
-- +-- yops/yops-9.config (no further imports)
159-
-- +-- yops/yops-7.config
160-
-- +-- yops-8.config
161-
-- +-- yops/yops-9.config (no further imports)
162-
-- +-- yops/yops-9.config (no further imports)
163-
--
164-
-- We don't check and don't error or warn on the same config being imported
165-
-- via many different paths.
166-
log "checking if we detect when the same config is imported via many different paths (we don't)"
167-
yopping <- cabal' "v2-build" [ "--project-file=yops-0.project" ]
168-
169136
log "checking bad conditional"
170137
badIf <- fails $ cabal' "v2-build" [ "--project-file=bad-conditional.project" ]
171138
assertOutputContains "Cannot set compiler in a conditional clause of a cabal project file" badIf

cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromSimple/cabal.test.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
import Test.Cabal.Prelude
22

3-
main = cabalTest . flakyIfCI 10975 . recordMode RecordMarked $ do
3+
main = cabalTest . flakyIfCI 10975 . flakyIfCI 10927 . recordMode RecordMarked $ do
44
let log = recordHeader . pure
55

66
out <- fails $ cabal' "v2-build" [ "all", "--dry-run" ]
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module Foo where
2+
3+
a :: Int
4+
a = 42

0 commit comments

Comments
 (0)