Skip to content

Commit aa35b73

Browse files
committed
Add data ProjectImport replacing tuples
1 parent 4c4b193 commit aa35b73

File tree

2 files changed

+19
-10
lines changed

2 files changed

+19
-10
lines changed

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

Lines changed: 15 additions & 6 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
@@ -46,6 +48,13 @@ import Text.PrettyPrint
4648
import Distribution.Simple.Utils (ordNub)
4749
import Distribution.System (OS(Windows), buildOS)
4850

51+
data ProjectImport =
52+
ProjectImport
53+
{ importOf :: FilePath
54+
, importBy :: ProjectConfigPath
55+
}
56+
deriving (Eq, Ord)
57+
4958
-- | Path to a configuration file, either a singleton project root, or a longer
5059
-- list representing a path to an import. The path is a non-empty list that we
5160
-- build up by prepending relative imports with @consProjectConfigPath@.
@@ -184,18 +193,18 @@ cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
184193
-- | A message for a duplicate import, a "duplicate import of". If a check for
185194
-- cyclical imports has already been made then this would report a duplicate
186195
-- import by two different paths.
187-
duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
196+
duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [ProjectImport] -> Doc
188197
duplicateImportMsg intro = seenImportMsg intro
189198

190-
seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc
191-
seenImportMsg intro duplicate path seenImportsBy =
199+
seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [ProjectImport] -> Doc
200+
seenImportMsg intro duplicate path seenImports =
192201
vcat
193202
[ intro
194203
, nest 2 (docProjectConfigPath path)
195204
, nest 2 $
196205
vcat
197-
[ docProjectConfigPath dib
198-
| (_, dib) <- filter ((duplicate ==) . fst) seenImportsBy
206+
[ docProjectConfigPath importBy
207+
| ProjectImport{importBy} <- filter ((duplicate ==) . importOf) seenImports
199208
]
200209
]
201210

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

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -260,7 +260,7 @@ parseProject rootPath cacheDir httpTransport verbosity configToParse = do
260260
let (dir, projectFileName) = splitFileName rootPath
261261
projectDir <- makeAbsolute dir
262262
projectPath@(ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [])
263-
importsBy <- newIORef $ toNubList [(canonicalRoot, projectPath)]
263+
importsBy <- newIORef $ toNubList [ProjectImport canonicalRoot projectPath]
264264
dupesMap <- newIORef mempty
265265
result <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir projectPath configToParse
266266
dupes <- Map.filter ((> 1) . length) <$> readIORef dupesMap
@@ -270,7 +270,7 @@ parseProject rootPath cacheDir httpTransport verbosity configToParse = do
270270
data Dupes = Dupes
271271
{ dupesUniqueImport :: FilePath
272272
, dupesNormLocPath :: ProjectConfigPath
273-
, dupesSeenImportsBy :: [(FilePath, ProjectConfigPath)]
273+
, dupesSeenImportsBy :: [ProjectImport]
274274
}
275275
deriving (Eq)
276276

@@ -289,7 +289,7 @@ parseProjectSkeleton
289289
:: FilePath
290290
-> HttpTransport
291291
-> Verbosity
292-
-> IORef (NubList (FilePath, ProjectConfigPath))
292+
-> IORef (NubList ProjectImport)
293293
-- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
294294
-> IORef DupesMap
295295
-- ^ The duplicates seen so far, used to defer reporting on duplicates
@@ -311,7 +311,7 @@ parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap project
311311
-- Once we canonicalize the import path, we can check for cyclical and duplicate imports
312312
normSource <- canonicalizeConfigPath projectDir source
313313
normLocPath@(ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath
314-
seenImportsBy@(fmap fst -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [(uniqueImport, normLocPath)] <> ibs, ibs))
314+
seenImportsBy@(fmap importOf -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [ProjectImport uniqueImport normLocPath] <> ibs, ibs))
315315
debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath)
316316
debug verbosity "\nseen unique paths\n================="
317317
mapM_ (debug verbosity) seenImports

0 commit comments

Comments
 (0)