Skip to content

Commit

Permalink
Add Y-forking import test
Browse files Browse the repository at this point in the history
- 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
  • Loading branch information
philderbeast committed Oct 22, 2024
1 parent cc2c9d8 commit 06065fb
Show file tree
Hide file tree
Showing 15 changed files with 127 additions and 19 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ module Distribution.Solver.Types.ProjectConfigPath
, docProjectConfigPath
, docProjectConfigPaths
, cyclicalImportMsg
, duplicateImportMsg
, docProjectConfigPathFailReason

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

-- | A message for a cyclical import, assuming the head of the path is the
-- duplicate.
-- | A message for a cyclical import, a "cyclical import of".
cyclicalImportMsg :: ProjectConfigPath -> Doc
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) = seenImportMsg "cyclical" duplicate path []

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

seenImportMsg :: String -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
seenImportMsg seen duplicate path seenImportsBy =
vcat
[ text "cyclical import of" <+> text duplicate <> semi
[ text seen <+> text "import of" <+> text duplicate <> semi
, nest 2 (docProjectConfigPath path)
, nest 2 $
vcat
[ docProjectConfigPath dib
| (_, dib) <- filter ((duplicate ==) . fst) seenImportsBy
]
]

docProjectConfigPathFailReason :: VR -> ProjectConfigPath -> Doc
Expand Down
43 changes: 28 additions & 15 deletions cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down Expand Up @@ -33,6 +34,7 @@ module Distribution.Client.ProjectConfig.Legacy
) where

import Data.Coerce (coerce)
import Data.IORef
import Distribution.Client.Compat.Prelude

import Distribution.Types.Flag (FlagName, parsecFlagAssignment)
Expand Down Expand Up @@ -137,7 +139,8 @@ import Distribution.Types.CondTree
)
import Distribution.Types.SourceRepo (RepoType)
import Distribution.Utils.NubList
( fromNubList
( NubList
, fromNubList
, overNubList
, toNubList
)
Expand Down Expand Up @@ -246,41 +249,51 @@ parseProject
parseProject rootPath cacheDir httpTransport verbosity configToParse = do
let (dir, projectFileName) = splitFileName rootPath
projectDir <- makeAbsolute dir
projectPath <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
parseProjectSkeleton cacheDir httpTransport verbosity projectDir projectPath configToParse
projectPath@(ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
importsBy <- newIORef $ toNubList [(canonicalRoot, projectPath)]
parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir projectPath configToParse

parseProjectSkeleton
:: FilePath
-> HttpTransport
-> Verbosity
-> IORef (NubList (FilePath, ProjectConfigPath))
-- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
-> FilePath
-- ^ The directory of the project configuration, typically the directory of cabal.project
-> ProjectConfigPath
-- ^ The path of the file being parsed, either the root or an import
-> ProjectConfigToParse
-- ^ The contents of the file to parse
-> IO (ParseResult ProjectConfigSkeleton)
parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir source (ProjectConfigToParse bs) =
(sanityWalkPCS False =<<) <$> liftPR (go []) (ParseUtils.readFields bs)
where
go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ParseResult ProjectConfigSkeleton)
go acc (x : xs) = case x of
(ParseUtils.F _ "import" importLoc) -> do
let importLocPath = importLoc `consProjectConfigPath` source

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

debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath)

if isCyclicConfigPath normLocPath
then pure . parseFail $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
else do
normSource <- canonicalizeConfigPath projectDir source
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
rest <- go [] xs
pure . fmap mconcat . sequence $ [fs, res, rest]
debug verbosity "\nseen unique paths\n================="
mapM_ (debug verbosity) seenImports
debug verbosity "\n"

if
| isCyclicConfigPath normLocPath ->
pure . parseFail $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing
| uniqueImport `elem` seenImports -> do
pure . parseFail $ ParseUtils.FromString (render $ duplicateImportMsg uniqueImport normLocPath seenImportsBy) Nothing
| otherwise -> do
normSource <- canonicalizeConfigPath projectDir source
let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc)
res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
rest <- go [] xs
pure . fmap mconcat . sequence $ [fs, res, rest]
(ParseUtils.Section l "if" p xs') -> do
subpcs <- go [] xs'
let fs = singletonProjectConfigSkeleton <$> fieldsToConfig source (reverse acc)
Expand Down
11 changes: 11 additions & 0 deletions cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,17 @@ Could not resolve dependencies:
(constraint from oops-0.project requires ==1.4.3.0)
[__1] fail (backjumping, conflict set: hashable, oops)
After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), oops (2)
# checking that we detect when the same config is imported via many different paths
# cabal v2-build
Error: [Cabal-7090]
Error parsing project file <ROOT>/yops-0.project:
duplicate import of yops/yops-3.config;
yops/yops-3.config
imported by: yops-0.project
yops/yops-3.config
imported by: yops-2.config
imported by: yops/yops-1.config
imported by: yops-0.project
# checking bad conditional
# cabal v2-build
Error: [Cabal-7090]
Expand Down
31 changes: 31 additions & 0 deletions cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -225,6 +225,37 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do
\ imported by: oops-0.project")
oopsing

-- The project is named yops as it is like hops but with y's for forks.
-- +-- yops-0.project
-- +-- yops/yops-1.config
-- +-- yops-2.config
-- +-- yops/yops-3.config
-- +-- yops-4.config
-- +-- yops/yops-5.config
-- +-- yops-6.config
-- +-- yops/yops-7.config
-- +-- yops-8.config
-- +-- yops/yops-9.config (no further imports)
-- +-- yops/yops-3.config
-- +-- yops-4.config
-- +-- yops/yops-5.config
-- +-- yops-6.config
-- +-- yops/yops-7.config
-- +-- yops-8.config
-- +-- yops/yops-9.config (no further imports)
-- +-- yops/yops-5.config
-- +-- yops-6.config
-- +-- yops/yops-7.config
-- +-- yops-8.config
-- +-- yops/yops-9.config (no further imports)
-- +-- yops/yops-7.config
-- +-- yops-8.config
-- +-- yops/yops-9.config (no further imports)
-- +-- yops/yops-9.config (no further imports)
log "checking that we detect when the same config is imported via many different paths"
yopping <- fails $ cabal' "v2-build" [ "--project-file=yops-0.project" ]
assertOutputContains "duplicate import of yops/yops-3.config" yopping

log "checking bad conditional"
badIf <- fails $ cabal' "v2-build" [ "--project-file=bad-conditional.project" ]
assertOutputContains "Cannot set compiler in a conditional clause of a cabal project file" badIf
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
packages: .

import: yops/yops-1.config
import: yops/yops-3.config
import: yops/yops-5.config
import: yops/yops-7.config
import: yops/yops-9.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: yops/yops-3.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: yops/yops-5.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: yops/yops-7.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: yops/yops-9.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: ../yops-2.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: ../yops-4.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: ../yops-6.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
import: ../yops-8.config
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
-- No imports here
23 changes: 23 additions & 0 deletions changelog.d/pr-9933
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
synopsis: Detect non-cyclical duplicate project imports
description:
Detect and report on duplicate imports that are non-cyclical and expand the
detail in cyclical import reporting, being more explicit and consistent with
non-cyclical duplicate reporting.

```
$ cabal build --project-file=yops-0.project
...
Error: [Cabal-7090]
Error parsing project file yops-0.project:
duplicate import of yops/yops-3.config;
yops/yops-3.config
imported by: yops-0.project
yops/yops-3.config
imported by: yops-2.config
imported by: yops/yops-1.config
imported by: yops-0.project
```

packages: cabal-install-solver cabal-install
prs: #9578 #9933
issues: #9562

0 comments on commit 06065fb

Please sign in to comment.