1
1
{-# LANGUAGE ConstraintKinds #-}
2
2
{-# LANGUAGE DataKinds #-}
3
3
{-# LANGUAGE DeriveGeneric #-}
4
- {-# LANGUAGE LambdaCase #-}
5
4
{-# LANGUAGE NamedFieldPuns #-}
6
5
{-# LANGUAGE PatternSynonyms #-}
7
6
{-# LANGUAGE RecordWildCards #-}
@@ -36,6 +35,7 @@ module Distribution.Client.ProjectConfig.Legacy
36
35
) where
37
36
38
37
import Data.Coerce (coerce )
38
+ import Data.IORef
39
39
import Distribution.Client.Compat.Prelude
40
40
41
41
import Distribution.Types.Flag (FlagName , parsecFlagAssignment )
@@ -145,7 +145,8 @@ import Distribution.Types.CondTree
145
145
)
146
146
import Distribution.Types.SourceRepo (RepoType )
147
147
import Distribution.Utils.NubList
148
- ( fromNubList
148
+ ( NubList
149
+ , fromNubList
149
150
, overNubList
150
151
, toNubList
151
152
)
@@ -197,7 +198,7 @@ import Distribution.Utils.Path hiding
197
198
)
198
199
199
200
import qualified Data.ByteString.Char8 as BS
200
- import Data.Functor ( (<&>) )
201
+ import Data.List ( sortOn )
201
202
import qualified Data.Map as Map
202
203
import qualified Data.Set as Set
203
204
import Network.URI (URI (.. ), nullURIAuth , parseURI )
@@ -206,9 +207,12 @@ import System.FilePath (isAbsolute, isPathSeparator, makeValid, splitFileName, (
206
207
import Text.PrettyPrint
207
208
( Doc
208
209
, render
210
+ , semi
211
+ , text
212
+ , vcat
209
213
, ($+$)
210
214
)
211
- import qualified Text.PrettyPrint as Disp
215
+ import qualified Text.PrettyPrint as Disp ( empty , int , render , text )
212
216
213
217
------------------------------------------------------------------
214
218
-- Handle extended project config files with conditionals and imports.
@@ -259,38 +263,66 @@ parseProject
259
263
-> ProjectConfigToParse
260
264
-- ^ The contents of the file to parse
261
265
-> 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
266
+ parseProject rootPath cacheDir httpTransport verbosity configToParse = do
267
+ let (dir, projectFileName) = splitFileName rootPath
268
+ projectDir <- makeAbsolute dir
269
+ projectPath@ (ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [] )
270
+ importsBy <- newIORef $ toNubList [(canonicalRoot, projectPath)]
271
+ dupesMap <- newIORef mempty
272
+ result <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir projectPath configToParse
273
+ dupes <- Map. filter ((> 1 ) . length ) <$> readIORef dupesMap
274
+ unless (Map. null dupes) (noticeDoc verbosity $ vcat (dupesMsg <$> Map. toList dupes))
275
+ return result
276
+
277
+ data Dupes = Dupes
278
+ { dupesUniqueImport :: FilePath
279
+ , dupesNormLocPath :: ProjectConfigPath
280
+ , dupesSeenImportsBy :: [(FilePath , ProjectConfigPath )]
281
+ }
282
+ deriving (Eq )
283
+
284
+ instance Ord Dupes where
285
+ compare = compare `on` length . dupesSeenImportsBy
286
+
287
+ type DupesMap = Map FilePath [Dupes ]
288
+
289
+ dupesMsg :: (FilePath , [Dupes ]) -> Doc
290
+ dupesMsg (duplicate, ds@ (take 1 . sortOn dupesNormLocPath -> dupes)) =
291
+ vcat $
292
+ ((text " Warning:" <+> Disp. int (length ds) <+> text " imports of" <+> text duplicate) <> semi)
293
+ : ((\ Dupes {.. } -> duplicateImportMsg Disp. empty dupesUniqueImport dupesNormLocPath dupesSeenImportsBy) <$> dupes)
270
294
271
295
parseProjectSkeleton
272
296
:: FilePath
273
297
-> HttpTransport
274
298
-> Verbosity
299
+ -> IORef (NubList (FilePath , ProjectConfigPath ))
300
+ -- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
301
+ -> IORef DupesMap
302
+ -- ^ The duplicates seen so far, used to defer reporting on duplicates
275
303
-> FilePath
276
304
-- ^ The directory of the project configuration, typically the directory of cabal.project
277
305
-> ProjectConfigPath
278
306
-- ^ The path of the file being parsed, either the root or an import
279
307
-> ProjectConfigToParse
280
308
-- ^ The contents of the file to parse
281
309
-> IO (ProjectParseResult ProjectConfigSkeleton )
282
- parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
310
+ parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir source (ProjectConfigToParse bs) =
283
311
(sanityWalkPCS False =<< ) <$> liftPR source (go [] ) (ParseUtils. readFields bs)
284
312
where
285
313
go :: [ParseUtils. Field ] -> [ParseUtils. Field ] -> IO (ProjectParseResult ProjectConfigSkeleton )
286
314
go acc (x : xs) = case x of
287
315
(ParseUtils. F _ " import" importLoc) -> do
288
316
let importLocPath = importLoc `consProjectConfigPath` source
289
317
290
- -- Once we canonicalize the import path, we can check for cyclical imports
318
+ -- Once we canonicalize the import path, we can check for cyclical and duplicate imports
291
319
normSource <- canonicalizeConfigPath projectDir source
292
- normLocPath <- canonicalizeConfigPath projectDir importLocPath
320
+ normLocPath@ (ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath
321
+ seenImportsBy@ (fmap fst -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ ibs -> (toNubList [(uniqueImport, normLocPath)] <> ibs, ibs))
293
322
debug verbosity $ " \n import path, normalized\n =======================\n " ++ render (docProjectConfigPath normLocPath)
323
+ debug verbosity " \n seen unique paths\n ================="
324
+ mapM_ (debug verbosity) seenImports
325
+ debug verbosity " \n "
294
326
295
327
if isCyclicConfigPath normLocPath
296
328
then pure . projectParseFail Nothing (Just normSource) $ ParseUtils. FromString (render $ cyclicalImportMsg normLocPath) Nothing
@@ -299,8 +331,10 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project
299
331
(isUntrimmedUriConfigPath importLocPath)
300
332
(noticeDoc verbosity $ untrimmedUriImportMsg (Disp. text " Warning:" ) importLocPath)
301
333
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
334
+ let uniqueFields = if uniqueImport `elem` seenImports then [] else xs
335
+ atomicModifyIORef' dupesMap $ \ dm -> (Map. insertWith (++) uniqueImport [Dupes uniqueImport normLocPath seenImportsBy] dm, () )
336
+ res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
337
+ rest <- go [] uniqueFields
304
338
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
305
339
(ParseUtils. Section l " if" p xs') -> do
306
340
normSource <- canonicalizeConfigPath projectDir source
0 commit comments