Skip to content

Commit 06065fb

Browse files
committed
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
1 parent cc2c9d8 commit 06065fb

File tree

15 files changed

+127
-19
lines changed

15 files changed

+127
-19
lines changed

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

Lines changed: 18 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Distribution.Solver.Types.ProjectConfigPath
1212
, docProjectConfigPath
1313
, docProjectConfigPaths
1414
, cyclicalImportMsg
15+
, duplicateImportMsg
1516
, docProjectConfigPathFailReason
1617

1718
-- * Checks and Normalization
@@ -101,13 +102,26 @@ docProjectConfigPaths :: [ProjectConfigPath] -> Doc
101102
docProjectConfigPaths ps = vcat
102103
[ text "-" <+> text p | ProjectConfigPath (p :| _) <- ps ]
103104

104-
-- | A message for a cyclical import, assuming the head of the path is the
105-
-- duplicate.
105+
-- | A message for a cyclical import, a "cyclical import of".
106106
cyclicalImportMsg :: ProjectConfigPath -> Doc
107-
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
107+
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) = seenImportMsg "cyclical" duplicate path []
108+
109+
-- | A message for a duplicate import, a "duplicate import of". If a check for
110+
-- cyclical imports has already been made then this would report a duplicate
111+
-- import by two different paths.
112+
duplicateImportMsg :: FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
113+
duplicateImportMsg = seenImportMsg "duplicate"
114+
115+
seenImportMsg :: String -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
116+
seenImportMsg seen duplicate path seenImportsBy =
108117
vcat
109-
[ text "cyclical import of" <+> text duplicate <> semi
118+
[ text seen <+> text "import of" <+> text duplicate <> semi
110119
, nest 2 (docProjectConfigPath path)
120+
, nest 2 $
121+
vcat
122+
[ docProjectConfigPath dib
123+
| (_, dib) <- filter ((duplicate ==) . fst) seenImportsBy
124+
]
111125
]
112126

113127
docProjectConfigPathFailReason :: VR -> ProjectConfigPath -> Doc

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

Lines changed: 28 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE ConstraintKinds #-}
22
{-# LANGUAGE DataKinds #-}
33
{-# LANGUAGE DeriveGeneric #-}
4+
{-# LANGUAGE MultiWayIf #-}
45
{-# LANGUAGE NamedFieldPuns #-}
56
{-# LANGUAGE RecordWildCards #-}
67
{-# LANGUAGE ScopedTypeVariables #-}
@@ -33,6 +34,7 @@ module Distribution.Client.ProjectConfig.Legacy
3334
) where
3435

3536
import Data.Coerce (coerce)
37+
import Data.IORef
3638
import Distribution.Client.Compat.Prelude
3739

3840
import Distribution.Types.Flag (FlagName, parsecFlagAssignment)
@@ -137,7 +139,8 @@ import Distribution.Types.CondTree
137139
)
138140
import Distribution.Types.SourceRepo (RepoType)
139141
import Distribution.Utils.NubList
140-
( fromNubList
142+
( NubList
143+
, fromNubList
141144
, overNubList
142145
, toNubList
143146
)
@@ -246,41 +249,51 @@ parseProject
246249
parseProject rootPath cacheDir httpTransport verbosity configToParse = do
247250
let (dir, projectFileName) = splitFileName rootPath
248251
projectDir <- makeAbsolute dir
249-
projectPath <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
250-
parseProjectSkeleton cacheDir httpTransport verbosity projectDir projectPath configToParse
252+
projectPath@(ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
253+
importsBy <- newIORef $ toNubList [(canonicalRoot, projectPath)]
254+
parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir projectPath configToParse
251255

252256
parseProjectSkeleton
253257
:: FilePath
254258
-> HttpTransport
255259
-> Verbosity
260+
-> IORef (NubList (FilePath, ProjectConfigPath))
261+
-- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
256262
-> FilePath
257263
-- ^ The directory of the project configuration, typically the directory of cabal.project
258264
-> ProjectConfigPath
259265
-- ^ The path of the file being parsed, either the root or an import
260266
-> ProjectConfigToParse
261267
-- ^ The contents of the file to parse
262268
-> IO (ParseResult ProjectConfigSkeleton)
263-
parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
269+
parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir source (ProjectConfigToParse bs) =
264270
(sanityWalkPCS False =<<) <$> liftPR (go []) (ParseUtils.readFields bs)
265271
where
266272
go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ParseResult ProjectConfigSkeleton)
267273
go acc (x : xs) = case x of
268274
(ParseUtils.F _ "import" importLoc) -> do
269275
let importLocPath = importLoc `consProjectConfigPath` source
270276

271-
-- Once we canonicalize the import path, we can check for cyclical imports
272-
normLocPath <- canonicalizeConfigPath projectDir importLocPath
277+
-- Once we canonicalize the import path, we can check for cyclical and duplicate imports
278+
normLocPath@(ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath
279+
seenImportsBy@(fmap fst -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [(uniqueImport, normLocPath)] <> ibs, ibs))
273280

274281
debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath)
275-
276-
if isCyclicConfigPath normLocPath
277-
then pure . parseFail $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
278-
else do
279-
normSource <- canonicalizeConfigPath projectDir source
280-
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
281-
res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
282-
rest <- go [] xs
283-
pure . fmap mconcat . sequence $ [fs, res, rest]
282+
debug verbosity "\nseen unique paths\n================="
283+
mapM_ (debug verbosity) seenImports
284+
debug verbosity "\n"
285+
286+
if
287+
| isCyclicConfigPath normLocPath ->
288+
pure . parseFail $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
289+
| uniqueImport `elem` seenImports -> do
290+
pure . parseFail $ ParseUtils.FromString (render $ duplicateImportMsg uniqueImport normLocPath seenImportsBy) Nothing
291+
| otherwise -> do
292+
normSource <- canonicalizeConfigPath projectDir source
293+
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
294+
res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
295+
rest <- go [] xs
296+
pure . fmap mconcat . sequence $ [fs, res, rest]
284297
(ParseUtils.Section l "if" p xs') -> do
285298
subpcs <- go [] xs'
286299
let fs = singletonProjectConfigSkeleton <$> fieldsToConfig source (reverse acc)

cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -124,6 +124,17 @@ Could not resolve dependencies:
124124
(constraint from oops-0.project requires ==1.4.3.0)
125125
[__1] fail (backjumping, conflict set: hashable, oops)
126126
After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), oops (2)
127+
# checking that we detect when the same config is imported via many different paths
128+
# cabal v2-build
129+
Error: [Cabal-7090]
130+
Error parsing project file <ROOT>/yops-0.project:
131+
duplicate import of yops/yops-3.config;
132+
yops/yops-3.config
133+
imported by: yops-0.project
134+
yops/yops-3.config
135+
imported by: yops-2.config
136+
imported by: yops/yops-1.config
137+
imported by: yops-0.project
127138
# checking bad conditional
128139
# cabal v2-build
129140
Error: [Cabal-7090]

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

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -225,6 +225,37 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do
225225
\ imported by: oops-0.project")
226226
oopsing
227227

228+
-- The project is named yops as it is like hops but with y's for forks.
229+
-- +-- yops-0.project
230+
-- +-- yops/yops-1.config
231+
-- +-- yops-2.config
232+
-- +-- yops/yops-3.config
233+
-- +-- yops-4.config
234+
-- +-- yops/yops-5.config
235+
-- +-- yops-6.config
236+
-- +-- yops/yops-7.config
237+
-- +-- yops-8.config
238+
-- +-- yops/yops-9.config (no further imports)
239+
-- +-- yops/yops-3.config
240+
-- +-- yops-4.config
241+
-- +-- yops/yops-5.config
242+
-- +-- yops-6.config
243+
-- +-- yops/yops-7.config
244+
-- +-- yops-8.config
245+
-- +-- yops/yops-9.config (no further imports)
246+
-- +-- yops/yops-5.config
247+
-- +-- yops-6.config
248+
-- +-- yops/yops-7.config
249+
-- +-- yops-8.config
250+
-- +-- yops/yops-9.config (no further imports)
251+
-- +-- yops/yops-7.config
252+
-- +-- yops-8.config
253+
-- +-- yops/yops-9.config (no further imports)
254+
-- +-- yops/yops-9.config (no further imports)
255+
log "checking that we detect when the same config is imported via many different paths"
256+
yopping <- fails $ cabal' "v2-build" [ "--project-file=yops-0.project" ]
257+
assertOutputContains "duplicate import of yops/yops-3.config" yopping
258+
228259
log "checking bad conditional"
229260
badIf <- fails $ cabal' "v2-build" [ "--project-file=bad-conditional.project" ]
230261
assertOutputContains "Cannot set compiler in a conditional clause of a cabal project file" badIf
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
packages: .
2+
3+
import: yops/yops-1.config
4+
import: yops/yops-3.config
5+
import: yops/yops-5.config
6+
import: yops/yops-7.config
7+
import: yops/yops-9.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: yops/yops-3.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: yops/yops-5.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: yops/yops-7.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: yops/yops-9.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: ../yops-2.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: ../yops-4.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: ../yops-6.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
import: ../yops-8.config
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
-- No imports here

changelog.d/pr-9933

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
synopsis: Detect non-cyclical duplicate project imports
2+
description:
3+
Detect and report on duplicate imports that are non-cyclical and expand the
4+
detail in cyclical import reporting, being more explicit and consistent with
5+
non-cyclical duplicate reporting.
6+
7+
```
8+
$ cabal build --project-file=yops-0.project
9+
...
10+
Error: [Cabal-7090]
11+
Error parsing project file yops-0.project:
12+
duplicate import of yops/yops-3.config;
13+
yops/yops-3.config
14+
imported by: yops-0.project
15+
yops/yops-3.config
16+
imported by: yops-2.config
17+
imported by: yops/yops-1.config
18+
imported by: yops-0.project
19+
```
20+
21+
packages: cabal-install-solver cabal-install
22+
prs: #9578 #9933
23+
issues: #9562

0 commit comments

Comments
 (0)