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,18 +198,14 @@ 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 )
204
205
import System.Directory (createDirectoryIfMissing , makeAbsolute )
205
206
import System.FilePath (isAbsolute , isPathSeparator , makeValid , splitFileName , (</>) )
206
- import Text.PrettyPrint
207
- ( Doc
208
- , render
209
- , ($+$)
210
- )
211
- import qualified Text.PrettyPrint as Disp
207
+ import Text.PrettyPrint (Doc , int , render , semi , text , vcat , ($+$) )
208
+ import qualified Text.PrettyPrint as Disp (empty )
212
209
213
210
------------------------------------------------------------------
214
211
-- Handle extended project config files with conditionals and imports.
@@ -259,48 +256,79 @@ parseProject
259
256
-> ProjectConfigToParse
260
257
-- ^ The contents of the file to parse
261
258
-> 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
259
+ parseProject rootPath cacheDir httpTransport verbosity configToParse = do
260
+ let (dir, projectFileName) = splitFileName rootPath
261
+ projectDir <- makeAbsolute dir
262
+ projectPath@ (ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| [] )
263
+ importsBy <- newIORef $ toNubList [ProjectImport canonicalRoot projectPath]
264
+ dupesMap <- newIORef mempty
265
+ result <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir projectPath configToParse
266
+ dupes <- Map. filter ((> 1 ) . length ) <$> readIORef dupesMap
267
+ unless (Map. null dupes) (noticeDoc verbosity $ vcat (dupesMsg <$> Map. toList dupes))
268
+ return result
269
+
270
+ data Dupes = Dupes
271
+ { dupesImport :: ProjectImport
272
+ -- ^ The import that we're checking for duplicates.
273
+ , dupesImports :: [ProjectImport ]
274
+ -- ^ All the imports of this file.
275
+ }
276
+ deriving (Eq )
277
+
278
+ instance Ord Dupes where
279
+ compare = compare `on` length . dupesImports
280
+
281
+ type DupesMap = Map FilePath [Dupes ]
282
+
283
+ dupesMsg :: (FilePath , [Dupes ]) -> Doc
284
+ dupesMsg (duplicate, ds@ (take 1 . sortOn (importBy . dupesImport) -> dupes)) =
285
+ vcat $
286
+ ((text " Warning:" <+> int (length ds) <+> text " imports of" <+> text duplicate) <> semi)
287
+ : ((\ Dupes {.. } -> duplicateImportMsg Disp. empty dupesImport dupesImports) <$> dupes)
270
288
271
289
parseProjectSkeleton
272
290
:: FilePath
273
291
-> HttpTransport
274
292
-> Verbosity
293
+ -> IORef (NubList ProjectImport )
294
+ -- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles
295
+ -> IORef DupesMap
296
+ -- ^ The duplicates seen so far, used to defer reporting on duplicates
275
297
-> FilePath
276
298
-- ^ The directory of the project configuration, typically the directory of cabal.project
277
299
-> ProjectConfigPath
278
300
-- ^ The path of the file being parsed, either the root or an import
279
301
-> ProjectConfigToParse
280
302
-- ^ The contents of the file to parse
281
303
-> IO (ProjectParseResult ProjectConfigSkeleton )
282
- parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
304
+ parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir source (ProjectConfigToParse bs) =
283
305
(sanityWalkPCS False =<< ) <$> liftPR source (go [] ) (ParseUtils. readFields bs)
284
306
where
285
307
go :: [ParseUtils. Field ] -> [ParseUtils. Field ] -> IO (ProjectParseResult ProjectConfigSkeleton )
286
308
go acc (x : xs) = case x of
287
309
(ParseUtils. F _ " import" importLoc) -> do
288
310
let importLocPath = importLoc `consProjectConfigPath` source
289
311
290
- -- Once we canonicalize the import path, we can check for cyclical imports
312
+ -- Once we canonicalize the import path, we can check for cyclical and duplicate imports
291
313
normSource <- canonicalizeConfigPath projectDir source
292
- normLocPath <- canonicalizeConfigPath projectDir importLocPath
314
+ normLocPath@ (ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath
315
+ seenImportsBy@ (fmap importOf -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ ibs -> (toNubList [ProjectImport uniqueImport normLocPath] <> ibs, ibs))
293
316
debug verbosity $ " \n import path, normalized\n =======================\n " ++ render (docProjectConfigPath normLocPath)
317
+ debug verbosity " \n seen unique paths\n ================="
318
+ mapM_ (debug verbosity) seenImports
319
+ debug verbosity " \n "
294
320
295
321
if isCyclicConfigPath normLocPath
296
322
then pure . projectParseFail Nothing (Just normSource) $ ParseUtils. FromString (render $ cyclicalImportMsg normLocPath) Nothing
297
323
else do
298
324
when
299
325
(isUntrimmedUriConfigPath importLocPath)
300
- (noticeDoc verbosity $ untrimmedUriImportMsg (Disp. text " Warning:" ) importLocPath)
326
+ (noticeDoc verbosity $ untrimmedUriImportMsg (text " Warning:" ) importLocPath)
301
327
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
328
+ let uniqueFields = if uniqueImport `elem` seenImports then [] else xs
329
+ atomicModifyIORef' dupesMap $ \ dm -> (Map. insertWith (++) uniqueImport [Dupes (ProjectImport uniqueImport normLocPath) seenImportsBy] dm, () )
330
+ res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath
331
+ rest <- go [] uniqueFields
304
332
pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
305
333
(ParseUtils. Section l " if" p xs') -> do
306
334
normSource <- canonicalizeConfigPath projectDir source
@@ -1295,13 +1323,13 @@ parseLegacyProjectConfig rootConfig bs =
1295
1323
1296
1324
showLegacyProjectConfig :: LegacyProjectConfig -> String
1297
1325
showLegacyProjectConfig config =
1298
- Disp. render $
1326
+ render $
1299
1327
showConfig
1300
1328
(legacyProjectConfigFieldDescrs constraintSrc)
1301
1329
legacyPackageConfigSectionDescrs
1302
1330
legacyPackageConfigFGSectionDescrs
1303
1331
config
1304
- $+$ Disp. text " "
1332
+ $+$ text " "
1305
1333
where
1306
1334
-- Note: ConstraintSource is unused when pretty-printing. We fake
1307
1335
-- it here to avoid having to pass it on call-sites. It's not great
@@ -1312,13 +1340,13 @@ legacyProjectConfigFieldDescrs :: ConstraintSource -> [FieldDescr LegacyProjectC
1312
1340
legacyProjectConfigFieldDescrs constraintSrc =
1313
1341
[ newLineListField
1314
1342
" packages"
1315
- (Disp. text . renderPackageLocationToken)
1343
+ (text . renderPackageLocationToken)
1316
1344
parsePackageLocationTokenQ
1317
1345
legacyPackages
1318
1346
(\ v flags -> flags{legacyPackages = v})
1319
1347
, newLineListField
1320
1348
" optional-packages"
1321
- (Disp. text . renderPackageLocationToken)
1349
+ (text . renderPackageLocationToken)
1322
1350
parsePackageLocationTokenQ
1323
1351
legacyPackagesOptional
1324
1352
(\ v flags -> flags{legacyPackagesOptional = v})
@@ -1429,7 +1457,7 @@ legacySharedConfigFieldDescrs constraintSrc =
1429
1457
. addFields
1430
1458
[ commaNewLineListFieldParsec
1431
1459
" package-dbs"
1432
- (Disp. text . showPackageDb)
1460
+ (text . showPackageDb)
1433
1461
(fmap readPackageDb parsecToken)
1434
1462
configPackageDBs
1435
1463
(\ v conf -> conf{configPackageDBs = v})
@@ -1722,8 +1750,8 @@ legacyPackageConfigFieldDescrs =
1722
1750
in FieldDescr
1723
1751
name
1724
1752
( \ f -> case f of
1725
- Flag NoDumpBuildInfo -> Disp. text " False"
1726
- Flag DumpBuildInfo -> Disp. text " True"
1753
+ Flag NoDumpBuildInfo -> text " False"
1754
+ Flag DumpBuildInfo -> text " True"
1727
1755
_ -> Disp. empty
1728
1756
)
1729
1757
( \ line str _ -> case () of
@@ -1750,9 +1778,9 @@ legacyPackageConfigFieldDescrs =
1750
1778
in FieldDescr
1751
1779
name
1752
1780
( \ f -> case f of
1753
- Flag NoOptimisation -> Disp. text " False"
1754
- Flag NormalOptimisation -> Disp. text " True"
1755
- Flag MaximumOptimisation -> Disp. text " 2"
1781
+ Flag NoOptimisation -> text " False"
1782
+ Flag NormalOptimisation -> text " True"
1783
+ Flag MaximumOptimisation -> text " 2"
1756
1784
_ -> Disp. empty
1757
1785
)
1758
1786
( \ line str _ -> case () of
@@ -1775,10 +1803,10 @@ legacyPackageConfigFieldDescrs =
1775
1803
in FieldDescr
1776
1804
name
1777
1805
( \ f -> case f of
1778
- Flag NoDebugInfo -> Disp. text " False"
1779
- Flag MinimalDebugInfo -> Disp. text " 1"
1780
- Flag NormalDebugInfo -> Disp. text " True"
1781
- Flag MaximalDebugInfo -> Disp. text " 3"
1806
+ Flag NoDebugInfo -> text " False"
1807
+ Flag MinimalDebugInfo -> text " 1"
1808
+ Flag NormalDebugInfo -> text " True"
1809
+ Flag MaximalDebugInfo -> text " 3"
1782
1810
_ -> Disp. empty
1783
1811
)
1784
1812
( \ line str _ -> case () of
@@ -2103,6 +2131,6 @@ monoidFieldParsec name showF readF get' set =
2103
2131
-- otherwise are special syntax.
2104
2132
showTokenQ :: String -> Doc
2105
2133
showTokenQ " " = Disp. empty
2106
- showTokenQ x@ (' -' : ' -' : _) = Disp. text (show x)
2107
- showTokenQ x@ (' .' : [] ) = Disp. text (show x)
2134
+ showTokenQ x@ (' -' : ' -' : _) = text (show x)
2135
+ showTokenQ x@ (' .' : [] ) = text (show x)
2108
2136
showTokenQ x = showToken x
0 commit comments