11{-# LANGUAGE ConstraintKinds #-}
22{-# LANGUAGE DataKinds #-}
33{-# LANGUAGE DeriveGeneric #-}
4- {-# LANGUAGE LambdaCase #-}
54{-# LANGUAGE NamedFieldPuns #-}
65{-# LANGUAGE PatternSynonyms #-}
76{-# LANGUAGE RecordWildCards #-}
@@ -36,6 +35,7 @@ module Distribution.Client.ProjectConfig.Legacy
3635 ) where
3736
3837import Data.Coerce (coerce )
38+ import Data.IORef
3939import Distribution.Client.Compat.Prelude
4040
4141import Distribution.Types.Flag (FlagName , parsecFlagAssignment )
@@ -145,7 +145,8 @@ import Distribution.Types.CondTree
145145 )
146146import Distribution.Types.SourceRepo (RepoType )
147147import Distribution.Utils.NubList
148- ( fromNubList
148+ ( NubList
149+ , fromNubList
149150 , overNubList
150151 , toNubList
151152 )
@@ -197,18 +198,14 @@ import Distribution.Utils.Path hiding
197198 )
198199
199200import qualified Data.ByteString.Char8 as BS
200- import Data.Functor ( (<&>) )
201+ import Data.List ( sortOn )
201202import qualified Data.Map as Map
202203import qualified Data.Set as Set
203204import Network.URI (URI (.. ), nullURIAuth , parseURI )
204205import System.Directory (createDirectoryIfMissing , makeAbsolute )
205206import 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 )
212209
213210------------------------------------------------------------------
214211-- Handle extended project config files with conditionals and imports.
@@ -259,48 +256,79 @@ parseProject
259256 -> ProjectConfigToParse
260257 -- ^ The contents of the file to parse
261258 -> 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)
270288
271289parseProjectSkeleton
272290 :: FilePath
273291 -> HttpTransport
274292 -> 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
275297 -> FilePath
276298 -- ^ The directory of the project configuration, typically the directory of cabal.project
277299 -> ProjectConfigPath
278300 -- ^ The path of the file being parsed, either the root or an import
279301 -> ProjectConfigToParse
280302 -- ^ The contents of the file to parse
281303 -> IO (ProjectParseResult ProjectConfigSkeleton )
282- parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) =
304+ parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir source (ProjectConfigToParse bs) =
283305 (sanityWalkPCS False =<< ) <$> liftPR source (go [] ) (ParseUtils. readFields bs)
284306 where
285307 go :: [ParseUtils. Field ] -> [ParseUtils. Field ] -> IO (ProjectParseResult ProjectConfigSkeleton )
286308 go acc (x : xs) = case x of
287309 (ParseUtils. F _ " import" importLoc) -> do
288310 let importLocPath = importLoc `consProjectConfigPath` source
289311
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
291313 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))
293316 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 "
294320
295321 if isCyclicConfigPath normLocPath
296322 then pure . projectParseFail Nothing (Just normSource) $ ParseUtils. FromString (render $ cyclicalImportMsg normLocPath) Nothing
297323 else do
298324 when
299325 (isUntrimmedUriConfigPath importLocPath)
300- (noticeDoc verbosity $ untrimmedUriImportMsg (Disp. text " Warning:" ) importLocPath)
326+ (noticeDoc verbosity $ untrimmedUriImportMsg (text " Warning:" ) importLocPath)
301327 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
304332 pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest]
305333 (ParseUtils. Section l " if" p xs') -> do
306334 normSource <- canonicalizeConfigPath projectDir source
@@ -1295,13 +1323,13 @@ parseLegacyProjectConfig rootConfig bs =
12951323
12961324showLegacyProjectConfig :: LegacyProjectConfig -> String
12971325showLegacyProjectConfig config =
1298- Disp. render $
1326+ render $
12991327 showConfig
13001328 (legacyProjectConfigFieldDescrs constraintSrc)
13011329 legacyPackageConfigSectionDescrs
13021330 legacyPackageConfigFGSectionDescrs
13031331 config
1304- $+$ Disp. text " "
1332+ $+$ text " "
13051333 where
13061334 -- Note: ConstraintSource is unused when pretty-printing. We fake
13071335 -- it here to avoid having to pass it on call-sites. It's not great
@@ -1312,13 +1340,13 @@ legacyProjectConfigFieldDescrs :: ConstraintSource -> [FieldDescr LegacyProjectC
13121340legacyProjectConfigFieldDescrs constraintSrc =
13131341 [ newLineListField
13141342 " packages"
1315- (Disp. text . renderPackageLocationToken)
1343+ (text . renderPackageLocationToken)
13161344 parsePackageLocationTokenQ
13171345 legacyPackages
13181346 (\ v flags -> flags{legacyPackages = v})
13191347 , newLineListField
13201348 " optional-packages"
1321- (Disp. text . renderPackageLocationToken)
1349+ (text . renderPackageLocationToken)
13221350 parsePackageLocationTokenQ
13231351 legacyPackagesOptional
13241352 (\ v flags -> flags{legacyPackagesOptional = v})
@@ -1429,7 +1457,7 @@ legacySharedConfigFieldDescrs constraintSrc =
14291457 . addFields
14301458 [ commaNewLineListFieldParsec
14311459 " package-dbs"
1432- (Disp. text . showPackageDb)
1460+ (text . showPackageDb)
14331461 (fmap readPackageDb parsecToken)
14341462 configPackageDBs
14351463 (\ v conf -> conf{configPackageDBs = v})
@@ -1722,8 +1750,8 @@ legacyPackageConfigFieldDescrs =
17221750 in FieldDescr
17231751 name
17241752 ( \ 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"
17271755 _ -> Disp. empty
17281756 )
17291757 ( \ line str _ -> case () of
@@ -1750,9 +1778,9 @@ legacyPackageConfigFieldDescrs =
17501778 in FieldDescr
17511779 name
17521780 ( \ 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"
17561784 _ -> Disp. empty
17571785 )
17581786 ( \ line str _ -> case () of
@@ -1775,10 +1803,10 @@ legacyPackageConfigFieldDescrs =
17751803 in FieldDescr
17761804 name
17771805 ( \ 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"
17821810 _ -> Disp. empty
17831811 )
17841812 ( \ line str _ -> case () of
@@ -2103,6 +2131,6 @@ monoidFieldParsec name showF readF get' set =
21032131-- otherwise are special syntax.
21042132showTokenQ :: String -> Doc
21052133showTokenQ " " = 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)
21082136showTokenQ x = showToken x
0 commit comments