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