From b200ecad4d9be4549e86fe7430af4b47c903d94f Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Tue, 13 Feb 2024 14:10:39 -0500 Subject: [PATCH 01/13] Warn on duplicate non-cyclical project imports - Add Y-forking import test - A test for detecting when the same config is imported via many different paths - Error on duplicate imports - Do the filtering in duplicateImportMsg - Use duplicateImportMsg for cycles too - Add haddocks to IORef parameter - Add changelog entry - Use ordNub instead of nub - Use NubList - Share implement of duplicate and cyclical messages - Update expectation for non-cyclical duplicate import - Only show a warning - Add woops project with a time cost - Use noticeDoc instead of warn - Render duplicate imports - Add Ord instance for Dupes, sort on dupesNormLocPath - Fixups after rebase - Satisfy hlint - Remove -XMultiWayIf - Remove mention of yops from the changelog - Satisfy fix-whitespace - Test with a time cost of duplicate imports --- .../Solver/Types/ProjectConfigPath.hs | 18 +- .../Client/ProjectConfig/Legacy.hs | 68 ++- .../ConditionalAndImport/cabal.out | 417 +++++++++++++++++- .../ConditionalAndImport/cabal.test.hs | 10 +- .../ConditionalAndImport/woops-0.project | 7 + .../ConditionalAndImport/woops-2.config | 2 + .../ConditionalAndImport/woops-4.config | 2 + .../ConditionalAndImport/woops-6.config | 2 + .../ConditionalAndImport/woops-8.config | 2 + .../ConditionalAndImport/woops/woops-1.config | 2 + .../ConditionalAndImport/woops/woops-3.config | 2 + .../ConditionalAndImport/woops/woops-5.config | 2 + .../ConditionalAndImport/woops/woops-7.config | 2 + .../ConditionalAndImport/woops/woops-9.config | 2 + changelog.d/pr-9933 | 23 + 15 files changed, 538 insertions(+), 23 deletions(-) create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops-0.project create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops-2.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops-4.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops-6.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops-8.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-1.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-3.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-5.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-7.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-9.config create mode 100644 changelog.d/pr-9933 diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs index 257ba808aaa..cd506113893 100644 --- a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs +++ b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs @@ -16,6 +16,7 @@ module Distribution.Solver.Types.ProjectConfigPath , docProjectImportedBy , docProjectConfigFiles , cyclicalImportMsg + , duplicateImportMsg , untrimmedUriImportMsg , docProjectConfigPathFailReason , quoteUntrimmed @@ -187,9 +188,24 @@ docProjectConfigFiles ps = vcat -- | A message for a cyclical import, a "cyclical import of". cyclicalImportMsg :: ProjectConfigPath -> Doc cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) = + seenImportMsg (text "cyclical import of" <+> text duplicate <> semi) duplicate path [] + +-- | A message for a duplicate import, a "duplicate import of". If a check for +-- cyclical imports has already been made then this would report a duplicate +-- import by two different paths. +duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc +duplicateImportMsg intro = seenImportMsg intro + +seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc +seenImportMsg intro duplicate path seenImportsBy = vcat - [ text "cyclical import of" <+> text duplicate <> semi + [ intro , nest 2 (docProjectConfigPath path) + , nest 2 $ + vcat + [ docProjectConfigPath dib + | (_, dib) <- filter ((duplicate ==) . fst) seenImportsBy + ] ] -- | A message for an import that has leading or trailing spaces. diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index 32b3670b479..376ebe29ebc 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -1,7 +1,6 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE RecordWildCards #-} @@ -36,6 +35,7 @@ module Distribution.Client.ProjectConfig.Legacy ) where import Data.Coerce (coerce) +import Data.IORef import Distribution.Client.Compat.Prelude import Distribution.Types.Flag (FlagName, parsecFlagAssignment) @@ -145,7 +145,8 @@ import Distribution.Types.CondTree ) import Distribution.Types.SourceRepo (RepoType) import Distribution.Utils.NubList - ( fromNubList + ( NubList + , fromNubList , overNubList , toNubList ) @@ -197,7 +198,7 @@ import Distribution.Utils.Path hiding ) import qualified Data.ByteString.Char8 as BS -import Data.Functor ((<&>)) +import Data.List (sortOn) import qualified Data.Map as Map import qualified Data.Set as Set import Network.URI (URI (..), nullURIAuth, parseURI) @@ -206,9 +207,12 @@ import System.FilePath (isAbsolute, isPathSeparator, makeValid, splitFileName, ( import Text.PrettyPrint ( Doc , render + , semi + , text + , vcat , ($+$) ) -import qualified Text.PrettyPrint as Disp +import qualified Text.PrettyPrint as Disp (empty, int, render, text) ------------------------------------------------------------------ -- Handle extended project config files with conditionals and imports. @@ -259,19 +263,43 @@ parseProject -> ProjectConfigToParse -- ^ The contents of the file to parse -> IO (ProjectParseResult ProjectConfigSkeleton) -parseProject rootPath cacheDir httpTransport verbosity configToParse = - do - let (dir, projectFileName) = splitFileName rootPath - projectDir <- makeAbsolute dir - projectPath <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| []) - parseProjectSkeleton cacheDir httpTransport verbosity projectDir projectPath configToParse - -- NOTE: Reverse the warnings so they are in line number order. - <&> \case ProjectParseOk ws x -> ProjectParseOk (reverse ws) x; x -> x +parseProject rootPath cacheDir httpTransport verbosity configToParse = do + let (dir, projectFileName) = splitFileName rootPath + projectDir <- makeAbsolute dir + projectPath@(ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| []) + importsBy <- newIORef $ toNubList [(canonicalRoot, projectPath)] + dupesMap <- newIORef mempty + result <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir projectPath configToParse + dupes <- Map.filter ((> 1) . length) <$> readIORef dupesMap + unless (Map.null dupes) (noticeDoc verbosity $ vcat (dupesMsg <$> Map.toList dupes)) + return result + +data Dupes = Dupes + { dupesUniqueImport :: FilePath + , dupesNormLocPath :: ProjectConfigPath + , dupesSeenImportsBy :: [(FilePath, ProjectConfigPath)] + } + deriving (Eq) + +instance Ord Dupes where + compare = compare `on` length . dupesSeenImportsBy + +type DupesMap = Map FilePath [Dupes] + +dupesMsg :: (FilePath, [Dupes]) -> Doc +dupesMsg (duplicate, ds@(take 1 . sortOn dupesNormLocPath -> dupes)) = + vcat $ + ((text "Warning:" <+> Disp.int (length ds) <+> text "imports of" <+> text duplicate) <> semi) + : ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesUniqueImport dupesNormLocPath dupesSeenImportsBy) <$> dupes) parseProjectSkeleton :: FilePath -> HttpTransport -> Verbosity + -> IORef (NubList (FilePath, ProjectConfigPath)) + -- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles + -> IORef DupesMap + -- ^ The duplicates seen so far, used to defer reporting on duplicates -> FilePath -- ^ The directory of the project configuration, typically the directory of cabal.project -> ProjectConfigPath @@ -279,7 +307,7 @@ parseProjectSkeleton -> ProjectConfigToParse -- ^ The contents of the file to parse -> IO (ProjectParseResult ProjectConfigSkeleton) -parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) = +parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir source (ProjectConfigToParse bs) = (sanityWalkPCS False =<<) <$> liftPR source (go []) (ParseUtils.readFields bs) where go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ProjectParseResult ProjectConfigSkeleton) @@ -287,10 +315,14 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project (ParseUtils.F _ "import" importLoc) -> do let importLocPath = importLoc `consProjectConfigPath` source - -- Once we canonicalize the import path, we can check for cyclical imports + -- Once we canonicalize the import path, we can check for cyclical and duplicate imports normSource <- canonicalizeConfigPath projectDir source - normLocPath <- canonicalizeConfigPath projectDir importLocPath + normLocPath@(ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath + seenImportsBy@(fmap fst -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [(uniqueImport, normLocPath)] <> ibs, ibs)) debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath) + debug verbosity "\nseen unique paths\n=================" + mapM_ (debug verbosity) seenImports + debug verbosity "\n" if isCyclicConfigPath normLocPath then pure . projectParseFail Nothing (Just normSource) $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing @@ -299,8 +331,10 @@ parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (Project (isUntrimmedUriConfigPath importLocPath) (noticeDoc verbosity $ untrimmedUriImportMsg (Disp.text "Warning:") importLocPath) let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc) - res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath - rest <- go [] xs + let uniqueFields = if uniqueImport `elem` seenImports then [] else xs + atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes uniqueImport normLocPath seenImportsBy] dm, ()) + res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath + rest <- go [] uniqueFields pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest] (ParseUtils.Section l "if" p xs') -> do normSource <- canonicalizeConfigPath projectDir source diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out index 4e2cfe368c3..769d100d814 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out @@ -194,9 +194,424 @@ Could not resolve dependencies: (constraint from oops-0.project requires ==1.4.3.0) [__1] fail (backjumping, conflict set: hashable, oops) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), oops (2) -# checking if we detect when the same config is imported via many different paths (we don't) +# checking that we detect when the same config is imported via many different paths # cabal v2-build +Warning: 2 imports of yops-4.config; + yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops-6.config; + yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops-8.config; + yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-3.config; + yops/yops-3.config + imported by: yops-0.project + yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-5.config; + yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-7.config; + yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-9.config; + yops/yops-9.config + imported by: yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops/yops-9.config + imported by: yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project Up to date +# checking that we detect when the same config is imported via many different paths +# cabal v2-build +Warning: 10 imports of https://www.stackage.org/lts-21.25/cabal.config; + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops-4.config; + woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops-6.config; + woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops-8.config; + woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-3.config; + woops/woops-3.config + imported by: woops-0.project + woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-5.config; + woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-7.config; + woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-9.config; + woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Configuration is affected by the following files: +- woops-0.project +- woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project +- woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project +- woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project +- woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- woops/woops-1.config + imported by: woops-0.project +- woops/woops-3.config + imported by: woops-0.project +- woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project +- woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project +- woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project +- woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project +- https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Resolving dependencies... +Build profile: -w ghc-9.4.8 -O1 +In order, the following will be built: + - my-0.1 (lib:my) (first run) +Configuring my-0.1... +Preprocessing library for my-0.1... +Building library for my-0.1... # checking bad conditional # cabal v2-build Error: [Cabal-7167] diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs index 5bcf8726850..d31fb5ff360 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs @@ -160,11 +160,13 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- yops-8.config -- +-- yops/yops-9.config (no further imports) -- +-- yops/yops-9.config (no further imports) - -- - -- We don't check and don't error or warn on the same config being imported - -- via many different paths. - log "checking if we detect when the same config is imported via many different paths (we don't)" + log "checking that we detect when the same config is imported via many different paths" yopping <- cabal' "v2-build" [ "--project-file=yops-0.project" ] + assertOutputContains "Warning: 2 imports" yopping + + log "checking that we detect when the same config is imported via many different paths" + wooping <- cabal' "v2-build" [ "--project-file=woops-0.project" ] + assertOutputContains "Warning: 10 imports" wooping log "checking bad conditional" badIf <- fails $ cabal' "v2-build" [ "--project-file=bad-conditional.project" ] diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-0.project b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-0.project new file mode 100644 index 00000000000..79933c8c1cb --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-0.project @@ -0,0 +1,7 @@ +packages: . + +import: woops/woops-1.config +import: woops/woops-3.config +import: woops/woops-5.config +import: woops/woops-7.config +import: woops/woops-9.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-2.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-2.config new file mode 100644 index 00000000000..50deddaaef5 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-2.config @@ -0,0 +1,2 @@ +import: woops/woops-3.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-4.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-4.config new file mode 100644 index 00000000000..6ff8dfb3013 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-4.config @@ -0,0 +1,2 @@ +import: woops/woops-5.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-6.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-6.config new file mode 100644 index 00000000000..f32758b83e4 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-6.config @@ -0,0 +1,2 @@ +import: woops/woops-7.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-8.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-8.config new file mode 100644 index 00000000000..b9043ce7c5d --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops-8.config @@ -0,0 +1,2 @@ +import: woops/woops-9.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-1.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-1.config new file mode 100644 index 00000000000..1151046199a --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-1.config @@ -0,0 +1,2 @@ +import: ../woops-2.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-3.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-3.config new file mode 100644 index 00000000000..9bbcedeb506 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-3.config @@ -0,0 +1,2 @@ +import: ../woops-4.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-5.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-5.config new file mode 100644 index 00000000000..181577c4dfe --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-5.config @@ -0,0 +1,2 @@ +import: ../woops-6.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-7.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-7.config new file mode 100644 index 00000000000..c2d9821826a --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-7.config @@ -0,0 +1,2 @@ +import: ../woops-8.config +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-9.config b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-9.config new file mode 100644 index 00000000000..44d1cc5e562 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-9.config @@ -0,0 +1,2 @@ +-- No imports here +import: https://www.stackage.org/lts-21.25/cabal.config diff --git a/changelog.d/pr-9933 b/changelog.d/pr-9933 new file mode 100644 index 00000000000..3e94a44609a --- /dev/null +++ b/changelog.d/pr-9933 @@ -0,0 +1,23 @@ +synopsis: Detect non-cyclical duplicate project imports +description: + Detect and report on duplicate imports that are non-cyclical. Give more detail + when reporting cyclical imports. Be more explicit and consistent with + non-cyclical duplicate reporting. + + ``` + $ cabal build --project-file=cabal.project + ... + Error: [Cabal-7090] + Error parsing project file cabal.project: + duplicate import of config/config-3.config; + config/config-3.config + imported by: cabal.project + config/config-3.config + imported by: config-2.config + imported by: config/config-1.config + imported by: cabal.project + ``` + +packages: cabal-install-solver cabal-install +prs: #9578 #9933 +issues: #9562 From ee46dd8f356a985f142c0fffcb6a5d18a420afa1 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sat, 26 Apr 2025 20:49:59 -0400 Subject: [PATCH 02/13] Fewer imports from PrettyPrint qualified as Disp --- .../Client/ProjectConfig/Legacy.hs | 47 ++++++++----------- 1 file changed, 20 insertions(+), 27 deletions(-) diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index 376ebe29ebc..4cbdf707af5 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -204,15 +204,8 @@ import qualified Data.Set as Set import Network.URI (URI (..), nullURIAuth, parseURI) import System.Directory (createDirectoryIfMissing, makeAbsolute) import System.FilePath (isAbsolute, isPathSeparator, makeValid, splitFileName, ()) -import Text.PrettyPrint - ( Doc - , render - , semi - , text - , vcat - , ($+$) - ) -import qualified Text.PrettyPrint as Disp (empty, int, render, text) +import Text.PrettyPrint (Doc, int, render, semi, text, vcat, ($+$)) +import qualified Text.PrettyPrint as Disp (empty) ------------------------------------------------------------------ -- Handle extended project config files with conditionals and imports. @@ -289,7 +282,7 @@ type DupesMap = Map FilePath [Dupes] dupesMsg :: (FilePath, [Dupes]) -> Doc dupesMsg (duplicate, ds@(take 1 . sortOn dupesNormLocPath -> dupes)) = vcat $ - ((text "Warning:" <+> Disp.int (length ds) <+> text "imports of" <+> text duplicate) <> semi) + ((text "Warning:" <+> int (length ds) <+> text "imports of" <+> text duplicate) <> semi) : ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesUniqueImport dupesNormLocPath dupesSeenImportsBy) <$> dupes) parseProjectSkeleton @@ -329,7 +322,7 @@ parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap project else do when (isUntrimmedUriConfigPath importLocPath) - (noticeDoc verbosity $ untrimmedUriImportMsg (Disp.text "Warning:") importLocPath) + (noticeDoc verbosity $ untrimmedUriImportMsg (text "Warning:") importLocPath) let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc) let uniqueFields = if uniqueImport `elem` seenImports then [] else xs atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes uniqueImport normLocPath seenImportsBy] dm, ()) @@ -1329,13 +1322,13 @@ parseLegacyProjectConfig rootConfig bs = showLegacyProjectConfig :: LegacyProjectConfig -> String showLegacyProjectConfig config = - Disp.render $ + render $ showConfig (legacyProjectConfigFieldDescrs constraintSrc) legacyPackageConfigSectionDescrs legacyPackageConfigFGSectionDescrs config - $+$ Disp.text "" + $+$ text "" where -- Note: ConstraintSource is unused when pretty-printing. We fake -- it here to avoid having to pass it on call-sites. It's not great @@ -1346,13 +1339,13 @@ legacyProjectConfigFieldDescrs :: ConstraintSource -> [FieldDescr LegacyProjectC legacyProjectConfigFieldDescrs constraintSrc = [ newLineListField "packages" - (Disp.text . renderPackageLocationToken) + (text . renderPackageLocationToken) parsePackageLocationTokenQ legacyPackages (\v flags -> flags{legacyPackages = v}) , newLineListField "optional-packages" - (Disp.text . renderPackageLocationToken) + (text . renderPackageLocationToken) parsePackageLocationTokenQ legacyPackagesOptional (\v flags -> flags{legacyPackagesOptional = v}) @@ -1463,7 +1456,7 @@ legacySharedConfigFieldDescrs constraintSrc = . addFields [ commaNewLineListFieldParsec "package-dbs" - (Disp.text . showPackageDb) + (text . showPackageDb) (fmap readPackageDb parsecToken) configPackageDBs (\v conf -> conf{configPackageDBs = v}) @@ -1756,8 +1749,8 @@ legacyPackageConfigFieldDescrs = in FieldDescr name ( \f -> case f of - Flag NoDumpBuildInfo -> Disp.text "False" - Flag DumpBuildInfo -> Disp.text "True" + Flag NoDumpBuildInfo -> text "False" + Flag DumpBuildInfo -> text "True" _ -> Disp.empty ) ( \line str _ -> case () of @@ -1784,9 +1777,9 @@ legacyPackageConfigFieldDescrs = in FieldDescr name ( \f -> case f of - Flag NoOptimisation -> Disp.text "False" - Flag NormalOptimisation -> Disp.text "True" - Flag MaximumOptimisation -> Disp.text "2" + Flag NoOptimisation -> text "False" + Flag NormalOptimisation -> text "True" + Flag MaximumOptimisation -> text "2" _ -> Disp.empty ) ( \line str _ -> case () of @@ -1809,10 +1802,10 @@ legacyPackageConfigFieldDescrs = in FieldDescr name ( \f -> case f of - Flag NoDebugInfo -> Disp.text "False" - Flag MinimalDebugInfo -> Disp.text "1" - Flag NormalDebugInfo -> Disp.text "True" - Flag MaximalDebugInfo -> Disp.text "3" + Flag NoDebugInfo -> text "False" + Flag MinimalDebugInfo -> text "1" + Flag NormalDebugInfo -> text "True" + Flag MaximalDebugInfo -> text "3" _ -> Disp.empty ) ( \line str _ -> case () of @@ -2137,6 +2130,6 @@ monoidFieldParsec name showF readF get' set = -- otherwise are special syntax. showTokenQ :: String -> Doc showTokenQ "" = Disp.empty -showTokenQ x@('-' : '-' : _) = Disp.text (show x) -showTokenQ x@('.' : []) = Disp.text (show x) +showTokenQ x@('-' : '-' : _) = text (show x) +showTokenQ x@('.' : []) = text (show x) showTokenQ x = showToken x From a7664f39ae19f66789815f1b301d568d04331ec2 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sat, 26 Apr 2025 21:21:41 -0400 Subject: [PATCH 03/13] Add data ProjectImport replacing tuples --- .../Solver/Types/ProjectConfigPath.hs | 21 +++++++++++++------ .../Client/ProjectConfig/Legacy.hs | 8 +++---- 2 files changed, 19 insertions(+), 10 deletions(-) diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs index cd506113893..7cbc69f95ad 100644 --- a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs +++ b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs @@ -1,10 +1,12 @@ {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ViewPatterns #-} module Distribution.Solver.Types.ProjectConfigPath ( -- * Project Config Path Manipulation - ProjectConfigPath(..) + ProjectImport(..) + , ProjectConfigPath(..) , projectConfigPathRoot , nullProjectConfigPath , consProjectConfigPath @@ -48,6 +50,13 @@ import Text.PrettyPrint import Distribution.Simple.Utils (ordNub) import Distribution.System (OS(Windows), buildOS) +data ProjectImport = + ProjectImport + { importOf :: FilePath + , importBy :: ProjectConfigPath + } + deriving (Eq, Ord) + -- | Path to a configuration file, either a singleton project root, or a longer -- list representing a path to an import. The path is a non-empty list that we -- build up by prepending relative imports with @consProjectConfigPath@. @@ -193,18 +202,18 @@ cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) = -- | A message for a duplicate import, a "duplicate import of". If a check for -- cyclical imports has already been made then this would report a duplicate -- import by two different paths. -duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc +duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [ProjectImport] -> Doc duplicateImportMsg intro = seenImportMsg intro -seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [(FilePath, ProjectConfigPath)] -> Doc -seenImportMsg intro duplicate path seenImportsBy = +seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [ProjectImport] -> Doc +seenImportMsg intro duplicate path seenImports = vcat [ intro , nest 2 (docProjectConfigPath path) , nest 2 $ vcat - [ docProjectConfigPath dib - | (_, dib) <- filter ((duplicate ==) . fst) seenImportsBy + [ docProjectConfigPath importBy + | ProjectImport{importBy} <- filter ((duplicate ==) . importOf) seenImports ] ] diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index 4cbdf707af5..8d883f1f9e6 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -260,7 +260,7 @@ parseProject rootPath cacheDir httpTransport verbosity configToParse = do let (dir, projectFileName) = splitFileName rootPath projectDir <- makeAbsolute dir projectPath@(ProjectConfigPath (canonicalRoot :| _)) <- canonicalizeConfigPath projectDir (ProjectConfigPath $ projectFileName :| []) - importsBy <- newIORef $ toNubList [(canonicalRoot, projectPath)] + importsBy <- newIORef $ toNubList [ProjectImport canonicalRoot projectPath] dupesMap <- newIORef mempty result <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir projectPath configToParse dupes <- Map.filter ((> 1) . length) <$> readIORef dupesMap @@ -270,7 +270,7 @@ parseProject rootPath cacheDir httpTransport verbosity configToParse = do data Dupes = Dupes { dupesUniqueImport :: FilePath , dupesNormLocPath :: ProjectConfigPath - , dupesSeenImportsBy :: [(FilePath, ProjectConfigPath)] + , dupesSeenImportsBy :: [ProjectImport] } deriving (Eq) @@ -289,7 +289,7 @@ parseProjectSkeleton :: FilePath -> HttpTransport -> Verbosity - -> IORef (NubList (FilePath, ProjectConfigPath)) + -> IORef (NubList ProjectImport) -- ^ The imports seen so far, used to report on cycles and duplicates and to detect duplicates that are not cycles -> IORef DupesMap -- ^ The duplicates seen so far, used to defer reporting on duplicates @@ -311,7 +311,7 @@ parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap project -- Once we canonicalize the import path, we can check for cyclical and duplicate imports normSource <- canonicalizeConfigPath projectDir source normLocPath@(ProjectConfigPath (uniqueImport :| _)) <- canonicalizeConfigPath projectDir importLocPath - seenImportsBy@(fmap fst -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [(uniqueImport, normLocPath)] <> ibs, ibs)) + seenImportsBy@(fmap importOf -> seenImports) <- fromNubList <$> atomicModifyIORef' importsBy (\ibs -> (toNubList [ProjectImport uniqueImport normLocPath] <> ibs, ibs)) debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath) debug verbosity "\nseen unique paths\n=================" mapM_ (debug verbosity) seenImports From 10a45b3642be28c5bcf5587714f9edefe263d065 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sat, 26 Apr 2025 21:32:23 -0400 Subject: [PATCH 04/13] Combine fields as ProjectImport --- .../Distribution/Solver/Types/ProjectConfigPath.hs | 11 +++++++---- .../src/Distribution/Client/ProjectConfig/Legacy.hs | 9 ++++----- 2 files changed, 11 insertions(+), 9 deletions(-) diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs index 7cbc69f95ad..445e21b3f38 100644 --- a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs +++ b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs @@ -197,16 +197,19 @@ docProjectConfigFiles ps = vcat -- | A message for a cyclical import, a "cyclical import of". cyclicalImportMsg :: ProjectConfigPath -> Doc cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) = - seenImportMsg (text "cyclical import of" <+> text duplicate <> semi) duplicate path [] + seenImportMsg + (text "cyclical import of" <+> text duplicate <> semi) + (ProjectImport duplicate path) + [] -- | A message for a duplicate import, a "duplicate import of". If a check for -- cyclical imports has already been made then this would report a duplicate -- import by two different paths. -duplicateImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [ProjectImport] -> Doc +duplicateImportMsg :: Doc -> ProjectImport -> [ProjectImport] -> Doc duplicateImportMsg intro = seenImportMsg intro -seenImportMsg :: Doc -> FilePath -> ProjectConfigPath -> [ProjectImport] -> Doc -seenImportMsg intro duplicate path seenImports = +seenImportMsg :: Doc -> ProjectImport -> [ProjectImport] -> Doc +seenImportMsg intro ProjectImport{importOf = duplicate, importBy = path} seenImports = vcat [ intro , nest 2 (docProjectConfigPath path) diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index 8d883f1f9e6..f177eb6fbce 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -268,8 +268,7 @@ parseProject rootPath cacheDir httpTransport verbosity configToParse = do return result data Dupes = Dupes - { dupesUniqueImport :: FilePath - , dupesNormLocPath :: ProjectConfigPath + { dupesImport :: ProjectImport , dupesSeenImportsBy :: [ProjectImport] } deriving (Eq) @@ -280,10 +279,10 @@ instance Ord Dupes where type DupesMap = Map FilePath [Dupes] dupesMsg :: (FilePath, [Dupes]) -> Doc -dupesMsg (duplicate, ds@(take 1 . sortOn dupesNormLocPath -> dupes)) = +dupesMsg (duplicate, ds@(take 1 . sortOn (importBy . dupesImport) -> dupes)) = vcat $ ((text "Warning:" <+> int (length ds) <+> text "imports of" <+> text duplicate) <> semi) - : ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesUniqueImport dupesNormLocPath dupesSeenImportsBy) <$> dupes) + : ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesImport dupesSeenImportsBy) <$> dupes) parseProjectSkeleton :: FilePath @@ -325,7 +324,7 @@ parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap project (noticeDoc verbosity $ untrimmedUriImportMsg (text "Warning:") importLocPath) let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc) let uniqueFields = if uniqueImport `elem` seenImports then [] else xs - atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes uniqueImport normLocPath seenImportsBy] dm, ()) + atomicModifyIORef' dupesMap $ \dm -> (Map.insertWith (++) uniqueImport [Dupes (ProjectImport uniqueImport normLocPath) seenImportsBy] dm, ()) res <- parseProjectSkeleton cacheDir httpTransport verbosity importsBy dupesMap projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath rest <- go [] uniqueFields pure . fmap mconcat . sequence $ [projectParse Nothing normSource fs, res, rest] From 116cef064eb6bab991ab8e10fcf9cb5aa632ba8d Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sat, 26 Apr 2025 21:37:02 -0400 Subject: [PATCH 05/13] Rename field to dupesImports --- .../src/Distribution/Client/ProjectConfig/Legacy.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index f177eb6fbce..45cb5b086c9 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -269,12 +269,12 @@ parseProject rootPath cacheDir httpTransport verbosity configToParse = do data Dupes = Dupes { dupesImport :: ProjectImport - , dupesSeenImportsBy :: [ProjectImport] + , dupesImports :: [ProjectImport] } deriving (Eq) instance Ord Dupes where - compare = compare `on` length . dupesSeenImportsBy + compare = compare `on` length . dupesImports type DupesMap = Map FilePath [Dupes] @@ -282,7 +282,7 @@ dupesMsg :: (FilePath, [Dupes]) -> Doc dupesMsg (duplicate, ds@(take 1 . sortOn (importBy . dupesImport) -> dupes)) = vcat $ ((text "Warning:" <+> int (length ds) <+> text "imports of" <+> text duplicate) <> semi) - : ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesImport dupesSeenImportsBy) <$> dupes) + : ((\Dupes{..} -> duplicateImportMsg Disp.empty dupesImport dupesImports) <$> dupes) parseProjectSkeleton :: FilePath From aaa473aae2670c30614df4d0e8dd6fca8ed8fc46 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sat, 26 Apr 2025 22:05:01 -0400 Subject: [PATCH 06/13] Add haddocks to Dupes fields --- cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index 45cb5b086c9..23e07687fa1 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -269,7 +269,9 @@ parseProject rootPath cacheDir httpTransport verbosity configToParse = do data Dupes = Dupes { dupesImport :: ProjectImport + -- ^ The import that we're checking for duplicates. , dupesImports :: [ProjectImport] + -- ^ All the imports of this file. } deriving (Eq) From e396f5c9b54aceb8e7b1f3d2ff96e8516d0d646d Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 27 Apr 2025 05:51:15 -0400 Subject: [PATCH 07/13] Mark test as flaky - Any test accessing stackage seems susceptible --- .../ProjectImport/DedupUsingConfigFromSimple/cabal.test.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromSimple/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromSimple/cabal.test.hs index a99809e1c52..97abc2f93ec 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromSimple/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ProjectImport/DedupUsingConfigFromSimple/cabal.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude -main = cabalTest . flakyIfCI 10975 . recordMode RecordMarked $ do +main = cabalTest . flakyIfCI 10975 . flakyIfCI 10927 . recordMode RecordMarked $ do let log = recordHeader . pure out <- fails $ cabal' "v2-build" [ "all", "--dry-run" ] From e8d48943846eab178f3edf9ad558a5b109376c8c Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sat, 9 Aug 2025 22:13:06 -0400 Subject: [PATCH 08/13] Use legacy parser for path duplicates test --- .../ConditionalAndImport/cabal.out | 163 ------------------ .../ConditionalAndImport/cabal.test.hs | 4 +- 2 files changed, 2 insertions(+), 165 deletions(-) diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out index 769d100d814..8ac56b82428 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out @@ -442,169 +442,6 @@ Warning: 2 imports of woops/woops-9.config; imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Configuration is affected by the following files: -- woops-0.project -- woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project -- woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project -- woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project -- woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- woops/woops-1.config - imported by: woops-0.project -- woops/woops-3.config - imported by: woops-0.project -- woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project -- woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project -- woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project -- woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project -- https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project Resolving dependencies... Build profile: -w ghc-9.4.8 -O1 In order, the following will be built: diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs index d31fb5ff360..ab0f000ada8 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs @@ -161,11 +161,11 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- yops/yops-9.config (no further imports) -- +-- yops/yops-9.config (no further imports) log "checking that we detect when the same config is imported via many different paths" - yopping <- cabal' "v2-build" [ "--project-file=yops-0.project" ] + yopping <- cabal' "v2-build" [ "--project-file=yops-0.project", "--project-file-parser=legacy" ] assertOutputContains "Warning: 2 imports" yopping log "checking that we detect when the same config is imported via many different paths" - wooping <- cabal' "v2-build" [ "--project-file=woops-0.project" ] + wooping <- cabal' "v2-build" [ "--project-file=woops-0.project", "--project-file-parser=legacy" ] assertOutputContains "Warning: 10 imports" wooping log "checking bad conditional" From 6426b056c54c2a28f357128cd517fbaac68d449f Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 10 Aug 2025 06:33:46 -0400 Subject: [PATCH 09/13] Move unique duplicates to own test --- .../ConditionalAndImport/cabal.out | 255 ------------------ .../ConditionalAndImport/cabal.test.hs | 35 --- .../UniquePathDuplicates/cabal.test.hs | 45 ++++ .../repo/hashable-1.4.2.0/hashable.cabal | 3 + .../repo/hashable-1.4.3.0/hashable.cabal | 3 + .../repo/some-exe-0.0.1.0/Main.hs | 4 + .../repo/some-exe-0.0.1.0/some-exe.cabal | 9 + .../UniquePathDuplicates/with-ghc.config | 7 + .../UniquePathDuplicates}/woops-0.project | 0 .../UniquePathDuplicates}/woops-2.config | 0 .../UniquePathDuplicates}/woops-4.config | 0 .../UniquePathDuplicates}/woops-6.config | 0 .../UniquePathDuplicates}/woops-8.config | 0 .../woops/woops-1.config | 0 .../woops/woops-3.config | 0 .../woops/woops-5.config | 0 .../woops/woops-7.config | 0 .../woops/woops-9.config | 0 .../UniquePathDuplicates}/yops-0.project | 0 .../UniquePathDuplicates}/yops-2.config | 0 .../UniquePathDuplicates}/yops-4.config | 0 .../UniquePathDuplicates}/yops-6.config | 0 .../UniquePathDuplicates}/yops-8.config | 0 .../UniquePathDuplicates}/yops/yops-1.config | 0 .../UniquePathDuplicates}/yops/yops-3.config | 0 .../UniquePathDuplicates}/yops/yops-5.config | 0 .../UniquePathDuplicates}/yops/yops-7.config | 0 .../UniquePathDuplicates}/yops/yops-9.config | 0 28 files changed, 71 insertions(+), 290 deletions(-) create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops-0.project (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops-2.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops-4.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops-6.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops-8.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops/woops-1.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops/woops-3.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops/woops-5.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops/woops-7.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/woops/woops-9.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops-0.project (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops-2.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops-4.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops-6.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops-8.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops/yops-1.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops/yops-3.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops/yops-5.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops/yops-7.config (100%) rename cabal-testsuite/PackageTests/{ConditionalAndImport => ProjectImport/UniquePathDuplicates}/yops/yops-9.config (100%) diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out index 8ac56b82428..546c850b51d 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out @@ -194,261 +194,6 @@ Could not resolve dependencies: (constraint from oops-0.project requires ==1.4.3.0) [__1] fail (backjumping, conflict set: hashable, oops) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), oops (2) -# checking that we detect when the same config is imported via many different paths -# cabal v2-build -Warning: 2 imports of yops-4.config; - yops-4.config - imported by: yops/yops-3.config - imported by: yops-0.project - yops-4.config - imported by: yops/yops-3.config - imported by: yops-2.config - imported by: yops/yops-1.config - imported by: yops-0.project -Warning: 2 imports of yops-6.config; - yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-0.project - yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-2.config - imported by: yops/yops-1.config - imported by: yops-0.project -Warning: 2 imports of yops-8.config; - yops-8.config - imported by: yops/yops-7.config - imported by: yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-0.project - yops-8.config - imported by: yops/yops-7.config - imported by: yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-2.config - imported by: yops/yops-1.config - imported by: yops-0.project -Warning: 2 imports of yops/yops-3.config; - yops/yops-3.config - imported by: yops-0.project - yops/yops-3.config - imported by: yops-2.config - imported by: yops/yops-1.config - imported by: yops-0.project -Warning: 2 imports of yops/yops-5.config; - yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-0.project - yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-2.config - imported by: yops/yops-1.config - imported by: yops-0.project -Warning: 2 imports of yops/yops-7.config; - yops/yops-7.config - imported by: yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-0.project - yops/yops-7.config - imported by: yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-2.config - imported by: yops/yops-1.config - imported by: yops-0.project -Warning: 2 imports of yops/yops-9.config; - yops/yops-9.config - imported by: yops-8.config - imported by: yops/yops-7.config - imported by: yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-0.project - yops/yops-9.config - imported by: yops-8.config - imported by: yops/yops-7.config - imported by: yops-6.config - imported by: yops/yops-5.config - imported by: yops-4.config - imported by: yops/yops-3.config - imported by: yops-2.config - imported by: yops/yops-1.config - imported by: yops-0.project -Up to date -# checking that we detect when the same config is imported via many different paths -# cabal v2-build -Warning: 10 imports of https://www.stackage.org/lts-21.25/cabal.config; - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Warning: 2 imports of woops-4.config; - woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project - woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Warning: 2 imports of woops-6.config; - woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project - woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Warning: 2 imports of woops-8.config; - woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project - woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Warning: 2 imports of woops/woops-3.config; - woops/woops-3.config - imported by: woops-0.project - woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Warning: 2 imports of woops/woops-5.config; - woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project - woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Warning: 2 imports of woops/woops-7.config; - woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project - woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Warning: 2 imports of woops/woops-9.config; - woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-0.project - woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project -Resolving dependencies... -Build profile: -w ghc-9.4.8 -O1 -In order, the following will be built: - - my-0.1 (lib:my) (first run) -Configuring my-0.1... -Preprocessing library for my-0.1... -Building library for my-0.1... # checking bad conditional # cabal v2-build Error: [Cabal-7167] diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs index ab0f000ada8..2cec97c31cf 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs @@ -133,41 +133,6 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do readFileVerbatim "oops.expect.txt" >>= flip (assertOn isInfixOf multilineNeedleHaystack) oopsing . normalizePathSeparators - -- The project is named yops as it is like hops but with y's for forks. - -- +-- yops-0.project - -- +-- yops/yops-1.config - -- +-- yops-2.config - -- +-- yops/yops-3.config - -- +-- yops-4.config - -- +-- yops/yops-5.config - -- +-- yops-6.config - -- +-- yops/yops-7.config - -- +-- yops-8.config - -- +-- yops/yops-9.config (no further imports) - -- +-- yops/yops-3.config - -- +-- yops-4.config - -- +-- yops/yops-5.config - -- +-- yops-6.config - -- +-- yops/yops-7.config - -- +-- yops-8.config - -- +-- yops/yops-9.config (no further imports) - -- +-- yops/yops-5.config - -- +-- yops-6.config - -- +-- yops/yops-7.config - -- +-- yops-8.config - -- +-- yops/yops-9.config (no further imports) - -- +-- yops/yops-7.config - -- +-- yops-8.config - -- +-- yops/yops-9.config (no further imports) - -- +-- yops/yops-9.config (no further imports) - log "checking that we detect when the same config is imported via many different paths" - yopping <- cabal' "v2-build" [ "--project-file=yops-0.project", "--project-file-parser=legacy" ] - assertOutputContains "Warning: 2 imports" yopping - - log "checking that we detect when the same config is imported via many different paths" - wooping <- cabal' "v2-build" [ "--project-file=woops-0.project", "--project-file-parser=legacy" ] - assertOutputContains "Warning: 10 imports" wooping - log "checking bad conditional" badIf <- fails $ cabal' "v2-build" [ "--project-file=bad-conditional.project" ] assertOutputContains "Cannot set compiler in a conditional clause of a cabal project file" badIf diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs new file mode 100644 index 00000000000..1b90c21659e --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs @@ -0,0 +1,45 @@ +import Test.Cabal.Prelude +import Test.Cabal.OutputNormalizer +import Data.Function ((&)) +import Data.Functor ((<&>)) +import Data.List (isInfixOf) + +main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do + let log = recordHeader . pure + + -- The project is named yops as it is like hops but with y's for forks. + -- +-- yops-0.project + -- +-- yops/yops-1.config + -- +-- yops-2.config + -- +-- yops/yops-3.config + -- +-- yops-4.config + -- +-- yops/yops-5.config + -- +-- yops-6.config + -- +-- yops/yops-7.config + -- +-- yops-8.config + -- +-- yops/yops-9.config (no further imports) + -- +-- yops/yops-3.config + -- +-- yops-4.config + -- +-- yops/yops-5.config + -- +-- yops-6.config + -- +-- yops/yops-7.config + -- +-- yops-8.config + -- +-- yops/yops-9.config (no further imports) + -- +-- yops/yops-5.config + -- +-- yops-6.config + -- +-- yops/yops-7.config + -- +-- yops-8.config + -- +-- yops/yops-9.config (no further imports) + -- +-- yops/yops-7.config + -- +-- yops-8.config + -- +-- yops/yops-9.config (no further imports) + -- +-- yops/yops-9.config (no further imports) + log "checking that we detect when the same config is imported via many different paths" + yopping <- cabal' "v2-build" [ "--project-file=yops-0.project", "--project-file-parser=legacy" ] + assertOutputContains "Warning: 2 imports" yopping + + log "checking that we detect when the same config is imported via many different paths" + wooping <- cabal' "v2-build" [ "--project-file=woops-0.project", "--project-file-parser=legacy" ] + assertOutputContains "Warning: 10 imports" wooping + + return () \ No newline at end of file diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal new file mode 100644 index 00000000000..de0cf79f7d8 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal @@ -0,0 +1,3 @@ +cabal-version: 1.12 +name: hashable +version: 1.4.2.0 diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal new file mode 100644 index 00000000000..b6475a1f15a --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal @@ -0,0 +1,3 @@ +cabal-version: 1.12 +name: hashable +version: 1.4.3.0 diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs new file mode 100644 index 00000000000..33581fa8421 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs @@ -0,0 +1,4 @@ +module Main where + +main :: IO () +main = putStrLn "hello world" diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal new file mode 100644 index 00000000000..3a2e620d96e --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal @@ -0,0 +1,9 @@ +name: some-exe +version: 0.0.1.0 +license: BSD3 +cabal-version: >= 1.2 +build-type: Simple + +Executable some-exe + main-is: Main.hs + build-depends: base diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config new file mode 100644 index 00000000000..140a00be1b9 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config @@ -0,0 +1,7 @@ +-- WARNING: Override the `with-compiler: ghc-x.y.z` of the stackage import, of +-- https://www.stackage.org/nightly-yyyy-mm-dd/cabal.config. Otherwise tests +-- will fail with: +-- -Error: [Cabal-5490] +-- -Cannot find the program 'ghc'. User-specified path 'ghc-x.y.z' does not +-- refer to an executable and the program is not on the system path. +with-compiler: ghc diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-0.project b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-0.project similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops-0.project rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-0.project diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-2.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-2.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops-2.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-2.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-4.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-4.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops-4.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-4.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-6.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-6.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops-6.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-6.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops-8.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-8.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops-8.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-8.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-1.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-1.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-1.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-1.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-3.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-3.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-3.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-3.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-5.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-5.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-5.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-5.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-7.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-7.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-7.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-7.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-9.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-9.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/woops/woops-9.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-9.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops-0.project b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-0.project similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops-0.project rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-0.project diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops-2.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-2.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops-2.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-2.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops-4.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-4.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops-4.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-4.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops-6.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-6.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops-6.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-6.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops-8.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-8.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops-8.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops-8.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-1.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-1.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-1.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-1.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-3.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-3.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-3.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-3.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-5.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-5.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-5.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-5.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-7.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-7.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-7.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-7.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-9.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-9.config similarity index 100% rename from cabal-testsuite/PackageTests/ConditionalAndImport/yops/yops-9.config rename to cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/yops/yops-9.config From 2d659bfe8d34a70c889581608830c4eca9b332bc Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 10 Aug 2025 07:20:41 -0400 Subject: [PATCH 10/13] Add foo.cabal package so that packages exist --- .../ProjectImport/UniquePathDuplicates/Foo.hs | 4 + .../UniquePathDuplicates/cabal.out | 257 ++++++++++++++++++ .../UniquePathDuplicates/cabal.test.hs | 4 +- .../UniquePathDuplicates/foo.cabal | 9 + 4 files changed, 272 insertions(+), 2 deletions(-) create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/Foo.hs create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/foo.cabal diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/Foo.hs b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/Foo.hs new file mode 100644 index 00000000000..8a39fe134cf --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/Foo.hs @@ -0,0 +1,4 @@ +module Foo where + +a :: Int +a = 42 diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out new file mode 100644 index 00000000000..c29a3437807 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out @@ -0,0 +1,257 @@ +# cabal v2-update +Downloading the latest package list from test-local-repo +# checking that we detect when the same config is imported via many different paths +# cabal v2-build +Warning: 2 imports of yops-4.config; + yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops-6.config; + yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops-8.config; + yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-3.config; + yops/yops-3.config + imported by: yops-0.project + yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-5.config; + yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-7.config; + yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Warning: 2 imports of yops/yops-9.config; + yops/yops-9.config + imported by: yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-0.project + yops/yops-9.config + imported by: yops-8.config + imported by: yops/yops-7.config + imported by: yops-6.config + imported by: yops/yops-5.config + imported by: yops-4.config + imported by: yops/yops-3.config + imported by: yops-2.config + imported by: yops/yops-1.config + imported by: yops-0.project +Resolving dependencies... +Build profile: -w ghc- -O1 +In order, the following would be built: + - foo-0.1 (lib:foo) (first run) +# checking that we detect when the same config is imported via many different paths +# cabal v2-build +Warning: 10 imports of https://www.stackage.org/lts-21.25/cabal.config; + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project + https://www.stackage.org/lts-21.25/cabal.config + imported by: woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops-4.config; + woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops-6.config; + woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops-8.config; + woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-3.config; + woops/woops-3.config + imported by: woops-0.project + woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-5.config; + woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-7.config; + woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Warning: 2 imports of woops/woops-9.config; + woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-0.project + woops/woops-9.config + imported by: woops-8.config + imported by: woops/woops-7.config + imported by: woops-6.config + imported by: woops/woops-5.config + imported by: woops-4.config + imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config + imported by: woops-0.project +Resolving dependencies... +Build profile: -w ghc-9.4.8 -O1 +In order, the following would be built: + - foo-0.1 (lib:foo) (first run) diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs index 1b90c21659e..8b6b2e26415 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs @@ -35,11 +35,11 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- yops/yops-9.config (no further imports) -- +-- yops/yops-9.config (no further imports) log "checking that we detect when the same config is imported via many different paths" - yopping <- cabal' "v2-build" [ "--project-file=yops-0.project", "--project-file-parser=legacy" ] + yopping <- cabal' "v2-build" [ "--project-file=yops-0.project", "--project-file-parser=legacy", "--dry-run" ] assertOutputContains "Warning: 2 imports" yopping log "checking that we detect when the same config is imported via many different paths" - wooping <- cabal' "v2-build" [ "--project-file=woops-0.project", "--project-file-parser=legacy" ] + wooping <- cabal' "v2-build" [ "--project-file=woops-0.project", "--project-file-parser=legacy", "--dry-run" ] assertOutputContains "Warning: 10 imports" wooping return () \ No newline at end of file diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/foo.cabal b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/foo.cabal new file mode 100644 index 00000000000..232f27167bd --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/foo.cabal @@ -0,0 +1,9 @@ +name: foo +version: 0.1 +license: BSD3 +cabal-version: >=1.2 +build-type: Simple + +library + exposed-modules: Foo + build-depends: base From aed02689b0c8cf96aa511730a14aee0884a2ed7e Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 10 Aug 2025 07:24:43 -0400 Subject: [PATCH 11/13] Satisfy fix-whitespace --- .../ProjectImport/UniquePathDuplicates/cabal.test.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs index 8b6b2e26415..931705d36a7 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs @@ -42,4 +42,4 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do wooping <- cabal' "v2-build" [ "--project-file=woops-0.project", "--project-file-parser=legacy", "--dry-run" ] assertOutputContains "Warning: 10 imports" wooping - return () \ No newline at end of file + return () From e7d675e5903d72fdf388863247fa91aabd124e4e Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 10 Aug 2025 14:07:54 -0400 Subject: [PATCH 12/13] Use local version of lts-21.25 --- .../UniquePathDuplicates/cabal.out | 100 +- .../UniquePathDuplicates/with-ghc.config | 7 - .../UniquePathDuplicates/woops-2.config | 2 +- .../UniquePathDuplicates/woops-4.config | 2 +- .../UniquePathDuplicates/woops-6.config | 2 +- .../UniquePathDuplicates/woops-8.config | 2 +- .../UniquePathDuplicates/woops/woops-1.config | 2 +- .../UniquePathDuplicates/woops/woops-3.config | 3 +- .../UniquePathDuplicates/woops/woops-5.config | 2 +- .../UniquePathDuplicates/woops/woops-7.config | 2 +- .../UniquePathDuplicates/woops/woops-9.config | 2 +- .../www-stackage-org/lts-21.25.config | 3018 +++++++++++++++++ 12 files changed, 3078 insertions(+), 66 deletions(-) delete mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config create mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out index c29a3437807..21160536202 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out @@ -99,48 +99,37 @@ In order, the following would be built: - foo-0.1 (lib:foo) (first run) # checking that we detect when the same config is imported via many different paths # cabal v2-build -Warning: 10 imports of https://www.stackage.org/lts-21.25/cabal.config; - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-2.config - imported by: woops/woops-1.config - imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config +Warning: 2 imports of woops-4.config; + woops-4.config imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-4.config + woops-4.config imported by: woops/woops-3.config imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config +Warning: 2 imports of woops-6.config; + woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-6.config + woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config +Warning: 2 imports of woops-8.config; + woops-8.config imported by: woops/woops-7.config imported by: woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config - imported by: woops-2.config - imported by: woops/woops-1.config imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops-8.config + woops-8.config imported by: woops/woops-7.config imported by: woops-6.config imported by: woops/woops-5.config @@ -149,48 +138,50 @@ Warning: 10 imports of https://www.stackage.org/lts-21.25/cabal.config; imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project - https://www.stackage.org/lts-21.25/cabal.config - imported by: woops/woops-9.config - imported by: woops-8.config - imported by: woops/woops-7.config - imported by: woops-6.config - imported by: woops/woops-5.config - imported by: woops-4.config - imported by: woops/woops-3.config +Warning: 2 imports of woops/woops-3.config; + woops/woops-3.config + imported by: woops-0.project + woops/woops-3.config imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Warning: 2 imports of woops-4.config; - woops-4.config +Warning: 2 imports of woops/woops-5.config; + woops/woops-5.config + imported by: woops-4.config imported by: woops/woops-3.config imported by: woops-0.project - woops-4.config + woops/woops-5.config + imported by: woops-4.config imported by: woops/woops-3.config imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Warning: 2 imports of woops-6.config; - woops-6.config +Warning: 2 imports of woops/woops-7.config; + woops/woops-7.config + imported by: woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config imported by: woops-0.project - woops-6.config + woops/woops-7.config + imported by: woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Warning: 2 imports of woops-8.config; - woops-8.config +Warning: 2 imports of woops/woops-9.config; + woops/woops-9.config + imported by: woops-8.config imported by: woops/woops-7.config imported by: woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config imported by: woops-0.project - woops-8.config + woops/woops-9.config + imported by: woops-8.config imported by: woops/woops-7.config imported by: woops-6.config imported by: woops/woops-5.config @@ -199,32 +190,39 @@ Warning: 2 imports of woops-8.config; imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Warning: 2 imports of woops/woops-3.config; - woops/woops-3.config +Warning: 10 imports of www-stackage-org/lts-21.25.config; + www-stackage-org/lts-21.25.config + imported by: woops-2.config + imported by: woops/woops-1.config imported by: woops-0.project - woops/woops-3.config + www-stackage-org/lts-21.25.config + imported by: woops/woops-3.config imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Warning: 2 imports of woops/woops-5.config; - woops/woops-5.config + www-stackage-org/lts-21.25.config imported by: woops-4.config imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config imported by: woops-0.project - woops/woops-5.config + www-stackage-org/lts-21.25.config + imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Warning: 2 imports of woops/woops-7.config; - woops/woops-7.config + www-stackage-org/lts-21.25.config imported by: woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config imported by: woops-0.project - woops/woops-7.config + www-stackage-org/lts-21.25.config + imported by: woops/woops-7.config imported by: woops-6.config imported by: woops/woops-5.config imported by: woops-4.config @@ -232,16 +230,18 @@ Warning: 2 imports of woops/woops-7.config; imported by: woops-2.config imported by: woops/woops-1.config imported by: woops-0.project -Warning: 2 imports of woops/woops-9.config; - woops/woops-9.config + www-stackage-org/lts-21.25.config imported by: woops-8.config imported by: woops/woops-7.config imported by: woops-6.config imported by: woops/woops-5.config imported by: woops-4.config imported by: woops/woops-3.config + imported by: woops-2.config + imported by: woops/woops-1.config imported by: woops-0.project - woops/woops-9.config + www-stackage-org/lts-21.25.config + imported by: woops/woops-9.config imported by: woops-8.config imported by: woops/woops-7.config imported by: woops-6.config @@ -252,6 +252,6 @@ Warning: 2 imports of woops/woops-9.config; imported by: woops/woops-1.config imported by: woops-0.project Resolving dependencies... -Build profile: -w ghc-9.4.8 -O1 +Build profile: -w ghc- -O1 In order, the following would be built: - foo-0.1 (lib:foo) (first run) diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config deleted file mode 100644 index 140a00be1b9..00000000000 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/with-ghc.config +++ /dev/null @@ -1,7 +0,0 @@ --- WARNING: Override the `with-compiler: ghc-x.y.z` of the stackage import, of --- https://www.stackage.org/nightly-yyyy-mm-dd/cabal.config. Otherwise tests --- will fail with: --- -Error: [Cabal-5490] --- -Cannot find the program 'ghc'. User-specified path 'ghc-x.y.z' does not --- refer to an executable and the program is not on the system path. -with-compiler: ghc diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-2.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-2.config index 50deddaaef5..bfcc9f5ca03 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-2.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-2.config @@ -1,2 +1,2 @@ import: woops/woops-3.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-4.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-4.config index 6ff8dfb3013..5e72539b5bd 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-4.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-4.config @@ -1,2 +1,2 @@ import: woops/woops-5.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-6.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-6.config index f32758b83e4..ee6648a8e90 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-6.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-6.config @@ -1,2 +1,2 @@ import: woops/woops-7.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-8.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-8.config index b9043ce7c5d..9310455c702 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-8.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops-8.config @@ -1,2 +1,2 @@ import: woops/woops-9.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-1.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-1.config index 1151046199a..a01c49aef77 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-1.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-1.config @@ -1,2 +1,2 @@ import: ../woops-2.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: ../www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-3.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-3.config index 9bbcedeb506..9e595466161 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-3.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-3.config @@ -1,2 +1,3 @@ import: ../woops-4.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: ../www-stackage-org/lts-21.25.config + diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-5.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-5.config index 181577c4dfe..712d0dd962d 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-5.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-5.config @@ -1,2 +1,2 @@ import: ../woops-6.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: ../www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-7.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-7.config index c2d9821826a..c6e8daa30df 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-7.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-7.config @@ -1,2 +1,2 @@ import: ../woops-8.config -import: https://www.stackage.org/lts-21.25/cabal.config +import: ../www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-9.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-9.config index 44d1cc5e562..8f9ed87a8ad 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-9.config +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/woops/woops-9.config @@ -1,2 +1,2 @@ -- No imports here -import: https://www.stackage.org/lts-21.25/cabal.config +import: ../www-stackage-org/lts-21.25.config diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/www-stackage-org/lts-21.25.config b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/www-stackage-org/lts-21.25.config new file mode 100644 index 00000000000..04f7e085d85 --- /dev/null +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/www-stackage-org/lts-21.25.config @@ -0,0 +1,3018 @@ +-- NOTE: Due to revisions, this file may not work. See: +-- https://github.com/commercialhaskell/stackage-server/issues/232 + +-- Stackage snapshot from: http://www.stackage.org/snapshot/lts-21.25 +-- Please place this file next to your .cabal file as cabal.config +-- To only use tested packages, uncomment the following line: +-- remote-repo: stackage-lts-21.25:http://www.stackage.org/lts-21.25 +-- with-compiler: ghc-9.4.8 +constraints: abstract-deque ==0.3, + abstract-deque-tests ==0.3, + abstract-par ==0.3.3, + AC-Angle ==1.0, + acc ==0.2.0.3, + ace ==0.6, + acid-state ==0.16.1.3, + action-permutations ==0.0.0.1, + active ==0.2.1, + ad ==4.5.4, + ad-delcont ==0.3.0.0, + adjunctions ==4.4.2, + adler32 ==0.1.2.0, + advent-of-code-api ==0.2.9.1, + aern2-mp ==0.2.15.1, + aern2-real ==0.2.15, + aeson ==2.1.2.1, + aeson-attoparsec ==0.0.0, + aeson-casing ==0.2.0.0, + aeson-combinators ==0.1.1.0, + aeson-diff ==1.1.0.13, + aeson-extra ==0.5.1.2, + aeson-generic-compat ==0.0.2.0, + aeson-iproute ==0.3.0, + aeson-optics ==1.2.1, + aeson-picker ==0.1.0.6, + aeson-pretty ==0.8.9, + aeson-qq ==0.8.4, + aeson-schemas ==1.4.1.0, + aeson-typescript ==0.6.1.0, + aeson-value-parser ==0.19.7.2, + aeson-yak ==0.1.1.3, + aeson-yaml ==1.1.0.1, + Agda ==2.6.4.1, + agda2lagda ==0.2023.6.9, + al ==0.1.4.2, + alarmclock ==0.7.0.6, + alex ==3.3.0.0, + alex-meta ==0.3.0.13, + algebra ==4.3.1, + algebraic-graphs ==0.7, + align-audio ==0.0.0.1, + Allure ==0.11.0.0, + almost-fix ==0.0.2, + alsa-core ==0.5.0.1, + alsa-mixer ==0.3.0.1, + alsa-pcm ==0.6.1.1, + alsa-seq ==0.6.0.9, + alternative-vector ==0.0.0, + alternators ==1.0.0.0, + ALUT ==2.4.0.3, + amqp ==0.22.1, + amqp-utils ==0.6.3.2, + annotated-exception ==0.2.0.5, + annotated-wl-pprint ==0.7.0, + ansi-terminal ==0.11.5, + ansi-terminal-game ==1.9.2.0, + ansi-terminal-types ==0.11.5, + ansi-wl-pprint ==0.6.9, + ANum ==0.2.0.2, + aos-signature ==0.1.1, + apecs ==0.9.5, + api-field-json-th ==0.1.0.2, + api-maker ==0.1.0.6, + ap-normalize ==0.1.0.1, + appar ==0.1.8, + appendful ==0.1.0.0, + appendmap ==0.1.5, + apply-refact ==0.13.0.0, + apportionment ==0.0.0.4, + approximate ==0.3.5, + approximate-equality ==1.1.0.2, + app-settings ==0.2.0.12, + arbor-lru-cache ==0.1.1.1, + arithmoi ==0.12.1.0, + array installed, + array-memoize ==0.6.0, + arrow-extras ==0.1.0.1, + arrows ==0.4.4.2, + ascii ==1.7.0.1, + ascii-case ==1.0.1.3, + ascii-caseless ==0.0.0.1, + ascii-char ==1.0.1.0, + ascii-group ==1.0.0.16, + ascii-numbers ==1.2.0.1, + ascii-predicates ==1.0.1.3, + ascii-progress ==0.3.3.0, + ascii-superset ==1.3.0.1, + ascii-th ==1.2.0.1, + asn1-encoding ==0.9.6, + asn1-parse ==0.9.5, + asn1-types ==0.3.4, + assert-failure ==0.1.3.0, + assoc ==1.1, + astro ==0.4.3.0, + async ==2.2.5, + async-extra ==0.2.0.0, + async-refresh ==0.3.0.0, + async-refresh-tokens ==0.4.0.0, + atom-basic ==0.2.5, + atom-conduit ==0.9.0.1, + atomic-primops ==0.8.4, + atomic-write ==0.2.0.7, + attoparsec ==0.14.4, + attoparsec-aeson ==2.1.0.0, + attoparsec-base64 ==0.0.0, + attoparsec-binary ==0.2, + attoparsec-data ==1.0.5.4, + attoparsec-expr ==0.1.1.2, + attoparsec-framer ==0.1.0.1, + attoparsec-iso8601 ==1.1.0.0, + attoparsec-path ==0.0.0.1, + attoparsec-run ==0.0.2.0, + attoparsec-time ==1.0.3.1, + audacity ==0.0.2.1, + authenticate ==1.3.5.2, + authenticate-oauth ==1.7, + autodocodec ==0.2.2.0, + autodocodec-openapi3 ==0.2.1.1, + autodocodec-schema ==0.1.0.3, + autodocodec-yaml ==0.2.0.3, + autoexporter ==2.0.0.9, + auto-update ==0.1.6, + avro ==0.6.1.2, + aws ==0.24.1, + aws-cloudfront-signed-cookies ==0.2.0.12, + aws-lambda-haskell-runtime ==4.1.2, + aws-lambda-haskell-runtime-wai ==2.0.2, + aws-sns-verify ==0.0.0.2, + aws-xray-client ==0.1.0.2, + aws-xray-client-persistent ==0.1.0.5, + aws-xray-client-wai ==0.1.0.2, + backtracking ==0.1.0, + bank-holidays-england ==0.2.0.9, + barbies ==2.0.5.0, + base installed, + base16 ==0.3.2.1, + base16-bytestring ==1.0.2.0, + base32 ==0.3.1.0, + base32string ==0.9.1, + base58-bytestring ==0.1.0, + base58string ==0.10.0, + base64 ==0.4.2.4, + base64-bytestring ==1.2.1.0, + base64-bytestring-type ==1.0.1, + base64-string ==0.2, + base-compat ==0.12.3, + base-compat-batteries ==0.12.3, + basement ==0.0.16, + base-orphans ==0.9.1, + base-prelude ==1.6.1.1, + base-unicode-symbols ==0.2.4.2, + basic-prelude ==0.7.0, + battleship-combinatorics ==0.0.1, + bazel-runfiles ==0.12, + bbdb ==0.8, + bcp47 ==0.2.0.6, + bcp47-orphans ==0.1.0.6, + bcrypt ==0.0.11, + bech32 ==1.1.3, + bech32-th ==1.1.1, + bench ==1.0.12, + benchpress ==0.2.2.23, + bencode ==0.6.1.1, + bencoding ==0.4.5.4, + benri-hspec ==0.1.0.1, + between ==0.11.0.0, + bhoogle ==0.1.4.2, + bibtex ==0.1.0.7, + bifunctor-classes-compat ==0.1, + bifunctors ==5.5.15, + bimap ==0.5.0, + bimaps ==0.1.0.2, + bimap-server ==0.1.0.1, + bin ==0.1.3, + binance-exports ==0.1.2.0, + binary installed, + binary-conduit ==1.3.1, + binaryen ==0.0.6.0, + binary-generic-combinators ==0.4.4.0, + binary-ieee754 ==0.1.0.0, + binary-instances ==1.0.4, + binary-list ==1.1.1.2, + binary-orphans ==1.0.4.1, + binary-parser ==0.5.7.5, + binary-search ==2.0.0, + binary-shared ==0.8.3, + binary-tagged ==0.3.1, + bindings-DSL ==1.0.25, + bindings-GLFW ==3.3.2.0, + bindings-libzip ==1.0.1, + bindings-uname ==0.1, + BiobaseEnsembl ==0.2.0.1, + bitarray ==0.0.1.1, + bits ==0.6, + bitset-word8 ==0.1.1.2, + bits-extra ==0.0.2.3, + bitvec ==1.1.5.0, + bitwise-enum ==1.0.1.2, + blake2 ==0.3.0, + Blammo ==1.1.2.1, + blank-canvas ==0.7.4, + blanks ==0.5.0, + blas-carray ==0.1.0.2, + blas-comfort-array ==0.0.0.3, + blas-ffi ==0.1, + blas-hs ==0.1.1.0, + blaze-bootstrap ==0.1.0.1, + blaze-builder ==0.4.2.3, + blaze-colonnade ==1.2.2.1, + blaze-html ==0.9.1.2, + blaze-markup ==0.8.3.0, + blaze-svg ==0.3.7, + blaze-textual ==0.2.3.1, + bloodhound ==0.21.0.0, + bm ==0.2.0.0, + bmp ==1.2.6.3, + bnb-staking-csvs ==0.2.1.0, + BNFC ==2.9.5, + BNFC-meta ==0.6.1, + board-games ==0.4, + bodhi ==0.1.0, + boltzmann-samplers ==0.1.1.0, + Boolean ==0.2.4, + boolsimplifier ==0.1.8, + boomerang ==1.4.9, + boots ==0.2.0.1, + bordacount ==0.1.0.0, + boring ==0.2.1, + bound ==2.0.7, + BoundedChan ==1.0.3.0, + bounded-queue ==1.0.0, + boundingboxes ==0.2.3, + box ==0.9.2.1, + boxes ==0.1.5, + breakpoint ==0.1.2.2, + brick ==1.9, + broadcast-chan ==0.2.1.2, + brotli ==0.0.0.1, + brotli-streams ==0.0.0.0, + bsb-http-chunked ==0.0.0.4, + bson ==0.4.0.1, + bson-lens ==0.1.1, + buffer-builder ==0.2.4.8, + buffer-pipe ==0.0, + bugsnag ==1.0.0.1, + bugsnag-haskell ==0.0.4.4, + bugsnag-hs ==0.2.0.12, + bugsnag-wai ==1.0.0.1, + bugsnag-yesod ==1.0.1.0, + bugzilla-redhat ==1.0.1.1, + burrito ==2.0.1.7, + bv ==0.5, + byteable ==0.1.1, + bytebuild ==0.3.14.0, + byte-count-reader ==0.10.1.10, + bytedump ==1.0, + bytehash ==0.1.0.0, + byte-order ==0.1.3.0, + byteorder ==1.0.4, + bytes ==0.17.3, + byteset ==0.1.1.1, + byteslice ==0.2.12.0, + bytesmith ==0.3.10.0, + bytestring installed, + bytestring-builder ==0.10.8.2.0, + bytestring-lexing ==0.5.0.11, + bytestring-mmap ==0.2.2, + bytestring-strict-builder ==0.4.5.7, + bytestring-to-vector ==0.3.0.1, + bytestring-tree-builder ==0.2.7.11, + bytestring-trie ==0.2.7.2, + bz2 ==1.0.1.0, + bzlib-conduit ==0.3.0.2, + c14n ==0.1.0.3, + c2hs ==0.28.8, + Cabal installed, + cabal2nix ==2.19.1, + cabal2spec ==2.7.0, + cabal-appimage ==0.4.0.2, + cabal-clean ==0.2.20230609, + cabal-doctest ==1.0.9, + cabal-file ==0.1.1, + cabal-install ==3.8.1.0, + cabal-install-solver ==3.8.1.0, + cabal-rpm ==2.1.5, + Cabal-syntax installed, + cache ==0.1.3.0, + cached-json-file ==0.1.1, + cacophony ==0.10.1, + cairo ==0.13.10.0, + calendar-recycling ==0.0.0.1, + call-alloy ==0.4.0.3, + calligraphy ==0.1.6, + call-plantuml ==0.0.1.3, + call-stack ==0.4.0, + can-i-haz ==0.3.1.1, + capability ==0.5.0.1, + ca-province-codes ==1.0.0.0, + cardano-coin-selection ==1.0.1, + carray ==0.1.6.8, + casa-client ==0.0.2, + casa-types ==0.0.2, + cased ==0.1.0.0, + case-insensitive ==1.2.1.0, + cases ==0.1.4.2, + casing ==0.1.4.1, + cassava ==0.5.3.0, + cassava-conduit ==0.6.5, + cassava-megaparsec ==2.0.4, + cast ==0.1.0.2, + cborg ==0.2.10.0, + cborg-json ==0.2.6.0, + cdar-mBound ==0.1.0.4, + c-enum ==0.1.1.3, + cereal ==0.5.8.3, + cereal-conduit ==0.8.0, + cereal-text ==0.1.0.2, + cereal-unordered-containers ==0.1.0.1, + cereal-vector ==0.2.0.1, + cfenv ==0.1.0.0, + cgi ==3001.5.0.1, + chan ==0.0.4.1, + character-cases ==0.1.0.6, + charset ==0.3.10, + charsetdetect-ae ==1.1.0.4, + Chart ==1.9.5, + Chart-diagrams ==1.9.5.1, + ChasingBottoms ==1.3.1.12, + check-email ==1.0.2, + checkers ==0.6.0, + checksum ==0.0.0.1, + chimera ==0.3.4.0, + choice ==0.2.3, + chronologique ==0.3.1.3, + chronos ==1.1.5.1, + chronos-bench ==0.2.0.2, + chunked-data ==0.3.1, + cipher-aes ==0.2.11, + cipher-camellia ==0.0.2, + cipher-rc4 ==0.1.4, + circle-packing ==0.1.0.6, + circular ==0.4.0.3, + citeproc ==0.8.1, + classy-prelude ==1.5.0.3, + classy-prelude-conduit ==1.5.0, + classy-prelude-yesod ==1.5.0, + cleff ==0.3.3.0, + clientsession ==0.9.2.0, + Clipboard ==2.3.2.0, + clock ==0.8.4, + closed ==0.2.0.2, + clumpiness ==0.17.0.2, + ClustalParser ==1.3.0, + cmark-gfm ==0.2.6, + cmdargs ==0.10.22, + codec-beam ==0.2.0, + code-conjure ==0.5.6, + code-page ==0.2.1, + coinor-clp ==0.0.0.1, + cointracking-imports ==0.1.0.2, + collect-errors ==0.1.5.0, + co-log-concurrent ==0.5.1.0, + co-log-core ==0.3.2.1, + colonnade ==1.2.0.2, + Color ==0.3.3, + colorful-monoids ==0.2.1.3, + colorize-haskell ==1.0.1, + colour ==2.3.6, + colourista ==0.1.0.2, + columnar ==1.0.0.0, + combinatorial ==0.1.1, + comfort-array ==0.5.3, + comfort-array-shape ==0.0, + comfort-blas ==0.0.1, + comfort-fftw ==0.0.0.1, + comfort-glpk ==0.1, + comfort-graph ==0.0.4, + commonmark ==0.2.4.1, + commonmark-extensions ==0.2.5.1, + commonmark-pandoc ==0.2.2, + commutative ==0.0.2, + commutative-semigroups ==0.1.0.1, + comonad ==5.0.8, + comonad-extras ==4.0.1, + compactmap ==0.1.4.3, + compdata ==0.13.1, + compensated ==0.8.3, + compiler-warnings ==0.1.0, + componentm ==0.0.0.2, + componentm-devel ==0.0.0.2, + composable-associations ==0.1.0.0, + composition ==1.0.2.2, + composition-extra ==2.0.0, + composition-prelude ==3.0.0.2, + concise ==0.1.0.1, + concurrency ==1.11.0.3, + concurrent-extra ==0.7.0.12, + concurrent-output ==1.10.20, + concurrent-split ==0.0.1.1, + cond ==0.4.1.1, + conduino ==0.2.4.0, + conduit ==1.3.5, + conduit-aeson ==0.1.0.1, + conduit-algorithms ==0.0.13.0, + conduit-combinators ==1.3.0, + conduit-concurrent-map ==0.1.3, + conduit-extra ==1.3.6, + conduit-parse ==0.2.1.1, + conduit-zstd ==0.0.2.0, + conferer ==1.1.0.0, + conferer-aeson ==1.1.0.2, + conferer-warp ==1.1.0.1, + ConfigFile ==1.1.4, + config-ini ==0.2.7.0, + configuration-tools ==0.6.1, + configurator ==0.3.0.0, + configurator-export ==0.1.0.1, + connection ==0.3.1, + console-style ==0.0.2.1, + constraints ==0.13.4, + constraints-extras ==0.4.0.0, + constraint-tuples ==0.1.2, + containers installed, + context ==0.2.0.3, + context-http-client ==0.2.0.2, + context-resource ==0.2.0.2, + context-wai-middleware ==0.2.0.2, + contiguous ==0.6.3.0, + contravariant ==1.5.5, + contravariant-extras ==0.3.5.4, + control-bool ==0.2.1, + control-dsl ==0.2.1.3, + control-monad-free ==0.6.2, + control-monad-omega ==0.3.2, + convertible ==1.1.1.1, + cookie ==0.4.6, + copr-api ==0.1.0, + core-data ==0.3.9.1, + core-program ==0.6.9.4, + core-telemetry ==0.2.9.4, + core-text ==0.3.8.1, + countable ==1.2, + country ==0.2.3.1, + covariance ==0.2.0.1, + cpphs ==1.20.9.1, + cprng-aes ==0.6.1, + cpu ==0.1.2, + cpuinfo ==0.1.0.2, + cql ==4.0.4, + cql-io ==1.1.1, + crackNum ==3.4, + crc32c ==0.1.0, + credential-store ==0.1.2, + criterion ==1.6.1.0, + criterion-measurement ==0.2.1.0, + cron ==0.7.0, + crypto-api ==0.13.3, + crypto-api-tests ==0.3, + crypto-cipher-tests ==0.0.11, + crypto-cipher-types ==0.0.9, + cryptocompare ==0.1.2, + crypto-enigma ==0.1.1.6, + cryptohash ==0.11.9, + cryptohash-cryptoapi ==0.1.4, + cryptohash-md5 ==0.11.101.0, + cryptohash-sha1 ==0.11.101.0, + cryptohash-sha256 ==0.11.102.1, + cryptohash-sha512 ==0.11.102.0, + crypton ==0.32, + crypton-conduit ==0.2.3, + cryptonite ==0.30, + cryptonite-conduit ==0.2.2, + cryptonite-openssl ==0.7, + crypto-pubkey-types ==0.4.3, + crypto-random ==0.0.9, + crypto-random-api ==0.2.0, + cryptostore ==0.3.0.1, + crypt-sha512 ==0, + csp ==1.4.0, + css-syntax ==0.1.0.1, + css-text ==0.1.3.0, + c-struct ==0.1.3.0, + csv ==0.1.2, + csv-conduit ==0.7.3.0, + ctrie ==0.2, + cubicbezier ==0.6.0.7, + cubicspline ==0.1.2, + cue-sheet ==2.0.2, + curl ==1.3.8, + curl-runnings ==0.17.0, + currency ==0.2.0.0, + currycarbon ==0.2.1.2, + cursor ==0.3.2.0, + cursor-brick ==0.1.0.1, + cursor-fuzzy-time ==0.0.0.0, + cursor-gen ==0.4.0.0, + cutter ==0.0, + cyclotomic ==1.1.2, + d10 ==1.0.1.3, + data-accessor ==0.2.3.1, + data-accessor-mtl ==0.2.0.5, + data-accessor-transformers ==0.2.1.8, + data-array-byte ==0.1.0.1, + data-binary-ieee754 ==0.4.4, + data-bword ==0.1.0.2, + data-checked ==0.3, + data-clist ==0.2, + data-compat ==0.1.0.4, + data-default ==0.7.1.1, + data-default-class ==0.1.2.0, + data-default-instances-base ==0.1.0.1, + data-default-instances-bytestring ==0.0.1, + data-default-instances-case-insensitive ==0.0.1, + data-default-instances-containers ==0.0.1, + data-default-instances-dlist ==0.0.1, + data-default-instances-old-locale ==0.0.1, + data-default-instances-unordered-containers ==0.0.1, + data-default-instances-vector ==0.0.1, + data-diverse ==4.7.1.0, + datadog ==0.3.0.0, + data-dword ==0.3.2.1, + data-endian ==0.1.1, + data-fix ==0.3.2, + data-forest ==0.1.0.12, + data-has ==0.4.0.0, + data-hash ==0.2.0.1, + data-interval ==2.1.1, + data-inttrie ==0.1.4, + data-lens-light ==0.1.2.4, + data-memocombinators ==0.5.1, + data-msgpack ==0.0.13, + data-msgpack-types ==0.0.3, + data-or ==1.0.0.7, + data-ordlist ==0.4.7.0, + data-ref ==0.1, + data-reify ==0.6.3, + data-serializer ==0.3.5, + data-sketches ==0.3.1.0, + data-sketches-core ==0.1.0.0, + data-textual ==0.3.0.3, + dataurl ==0.1.0.0, + DAV ==1.3.4, + dbcleaner ==0.1.3, + DBFunctor ==0.1.2.1, + dbus ==1.2.29, + dbus-hslogger ==0.1.0.1, + debian ==4.0.5, + debian-build ==0.10.2.1, + debug-trace-var ==0.2.0, + dec ==0.0.5, + Decimal ==0.5.2, + declarative ==0.5.4, + deepseq installed, + deepseq-generics ==0.2.0.0, + deferred-folds ==0.9.18.6, + dejafu ==2.4.0.5, + dense-linear-algebra ==0.1.0.0, + dependent-map ==0.4.0.0, + dependent-sum ==0.7.2.0, + depq ==0.4.2, + deque ==0.4.4.1, + deriveJsonNoPrefix ==0.1.0.1, + derive-storable ==0.3.1.0, + derive-topdown ==0.0.3.0, + deriving-aeson ==0.2.9, + deriving-compat ==0.6.5, + deriving-trans ==0.5.2.0, + detour-via-sci ==1.0.0, + df1 ==0.4.2, + dhall ==1.41.2, + dhall-bash ==1.0.40, + dhall-json ==1.7.11, + dhall-yaml ==1.2.12, + di ==1.3, + diagrams ==1.4.1, + diagrams-cairo ==1.4.2.1, + diagrams-canvas ==1.4.1.2, + diagrams-contrib ==1.4.5.1, + diagrams-core ==1.5.1.1, + diagrams-html5 ==1.4.2, + diagrams-lib ==1.4.6, + diagrams-postscript ==1.5.1.1, + diagrams-rasterific ==1.4.2.3, + diagrams-solve ==0.1.3, + diagrams-svg ==1.4.3.1, + dice ==0.1.1, + di-core ==1.0.4, + dictionary-sharing ==0.1.0.0, + di-df1 ==1.2.1, + Diff ==0.4.1, + diff-loc ==0.1.0.0, + digest ==0.0.2.0, + digits ==0.3.1, + di-handle ==1.0.1, + dimensional ==1.5, + di-monad ==1.3.5, + directory installed, + directory-tree ==0.12.1, + direct-sqlite ==2.3.28, + dirichlet ==0.1.0.7, + discount ==0.1.1, + discover-instances ==0.1.0.0, + discrimination ==0.5, + disk-free-space ==0.1.0.1, + distributed-static ==0.3.9, + distribution-nixpkgs ==1.7.0.1, + distribution-opensuse ==1.1.4, + distributive ==0.6.2.1, + diversity ==0.8.1.0, + djinn-lib ==0.0.1.4, + dl-fedora ==0.9.6, + dlist ==1.0, + dlist-instances ==0.1.1.1, + dlist-nonempty ==0.1.3, + dns ==4.1.1, + dockerfile ==0.2.0, + doclayout ==0.4.0.1, + doctemplates ==0.11, + doctest ==0.20.1, + doctest-discover ==0.2.0.0, + doctest-driver-gen ==0.3.0.8, + doctest-exitcode-stdio ==0.0, + doctest-extract ==0.1.1.1, + doctest-lib ==0.1, + doctest-parallel ==0.3.1, + doldol ==0.4.1.2, + do-list ==1.0.1, + domain ==0.1.1.5, + domain-aeson ==0.1.1.2, + domain-cereal ==0.1.0.1, + domain-core ==0.1.0.4, + domain-optics ==0.1.0.4, + do-notation ==0.1.0.2, + dot ==0.3, + dotenv ==0.11.0.2, + dotgen ==0.4.3, + dotnet-timespan ==0.0.1.0, + double-conversion ==2.0.4.2, + download ==0.3.2.7, + download-curl ==0.1.4, + DPutils ==0.1.1.0, + drifter ==0.3.0, + drifter-postgresql ==0.2.1, + drifter-sqlite ==0.1.0.0, + dsp ==0.2.5.2, + dual ==0.1.1.1, + dual-tree ==0.2.3.1, + dublincore-xml-conduit ==0.1.0.3, + dunai ==0.11.2, + duration ==0.2.0.0, + dvorak ==0.1.0.0, + dynamic-state ==0.3.1, + dyre ==0.9.2, + eap ==0.9.0.2, + Earley ==0.13.0.1, + easy-file ==0.2.5, + easy-logger ==0.1.0.7, + Ebnf2ps ==1.0.15, + echo ==0.1.4, + ecstasy ==0.2.1.0, + ed25519 ==0.0.5.0, + ede ==0.3.3.0, + edit-distance ==0.2.2.1, + edit-distance-vector ==1.0.0.4, + editor-open ==0.6.0.0, + effectful ==2.2.2.0, + effectful-core ==2.2.2.2, + effectful-plugin ==1.1.0.2, + effectful-th ==1.0.0.1, + either ==5.0.2, + either-both ==0.1.1.1, + either-unwrap ==1.1, + ekg-core ==0.1.1.7, + elerea ==2.9.0, + elf ==0.31, + eliminators ==0.9.2, + elm2nix ==0.3.1, + elm-bridge ==0.8.2, + elm-core-sources ==1.0.0, + elm-export ==0.6.0.1, + elynx ==0.7.2.2, + elynx-markov ==0.7.2.2, + elynx-nexus ==0.7.2.2, + elynx-seq ==0.7.2.2, + elynx-tools ==0.7.2.1, + elynx-tree ==0.7.2.2, + emacs-module ==0.1.1.1, + email-validate ==2.3.2.19, + emojis ==0.1.3, + enclosed-exceptions ==1.0.3, + ENIG ==0.0.1.0, + entropy ==0.4.1.10, + enummapset ==0.7.2.0, + enumset ==0.1, + enum-subset-generate ==0.1.0.1, + enum-text ==0.5.3.0, + envelope ==0.2.2.0, + envparse ==0.5.0, + envy ==2.1.2.0, + eq ==4.3, + equal-files ==0.0.5.4, + equational-reasoning ==0.7.0.1, + equivalence ==0.4.1, + erf ==2.0.0.0, + error ==1.0.0.0, + errorcall-eq-instance ==0.3.0, + error-or ==0.3.0, + error-or-utils ==0.2.0, + errors ==2.3.0, + errors-ext ==0.4.2, + ersatz ==0.4.13, + esqueleto ==3.5.11.0, + event-list ==0.1.2.1, + eventstore ==1.4.2, + every ==0.0.1, + evm-opcodes ==0.1.2, + exact-combinatorics ==0.2.0.11, + exact-pi ==0.5.0.2, + exception-hierarchy ==0.1.0.10, + exception-mtl ==0.4.0.2, + exceptions installed, + exception-transformers ==0.4.0.12, + executable-hash ==0.2.0.4, + executable-path ==0.0.3.1, + exinst ==0.9, + exit-codes ==1.0.0, + exomizer ==1.0.0, + experimenter ==0.1.0.14, + expiring-cache-map ==0.0.6.1, + explainable-predicates ==0.1.2.4, + explicit-exception ==0.2, + exp-pairs ==0.2.1.0, + express ==1.0.12, + extended-reals ==0.2.4.0, + extensible ==0.9, + extensible-effects ==5.0.0.1, + extensible-exceptions ==0.1.1.4, + extra ==1.7.14, + extractable-singleton ==0.0.1, + extrapolate ==0.4.6, + fail ==4.9.0.0, + failable ==1.2.4.0, + FailT ==0.1.2.0, + fakedata ==1.0.3, + fakedata-parser ==0.1.0.0, + fakedata-quickcheck ==0.2.0, + fakefs ==0.3.0.2, + fakepull ==0.3.0.2, + faktory ==1.1.2.4, + fasta ==0.10.4.2, + fast-logger ==3.2.2, + fast-math ==1.0.2, + fastmemo ==0.1.1, + fast-myers-diff ==0.0.0, + fb ==2.1.1.1, + fcf-family ==0.2.0.0, + fdo-notify ==0.3.1, + feature-flags ==0.1.0.1, + fedora-dists ==2.1.1, + fedora-haskell-tools ==1.0, + feed ==1.3.2.1, + FenwickTree ==0.1.2.1, + fft ==0.1.8.7, + fftw-ffi ==0.1, + fgl ==5.8.0.0, + fields-json ==0.4.0.0, + file-embed ==0.0.15.0, + file-embed-lzma ==0.0.1, + filelock ==0.1.1.7, + filemanip ==0.3.6.3, + file-modules ==0.1.2.4, + filepath installed, + filepath-bytestring ==1.4.2.1.13, + file-path-th ==0.1.0.0, + filepattern ==0.1.3, + fileplow ==0.1.0.0, + filter-logger ==0.6.0.0, + filtrable ==0.1.6.0, + fin ==0.3, + FindBin ==0.0.5, + fingertree ==0.1.5.0, + finite-typelits ==0.1.6.0, + first-class-families ==0.8.0.1, + first-class-patterns ==0.3.2.5, + fitspec ==0.4.10, + fixed ==0.3, + fixed-length ==0.2.3.1, + fixed-vector ==1.2.3.0, + fixed-vector-hetero ==0.6.1.1, + fix-whitespace ==0.0.11, + flac ==0.2.1, + flac-picture ==0.1.2, + flags-applicative ==0.1.0.3, + flat ==0.6, + flatparse ==0.4.1.0, + flay ==0.4, + FloatingHex ==0.5, + floatshow ==0.2.4, + flow ==2.0.0.4, + flush-queue ==1.0.0, + fmlist ==0.9.4, + fmt ==0.6.3.0, + fn ==0.3.0.2, + focus ==1.0.3.2, + focuslist ==0.1.1.0, + foldable1-classes-compat ==0.1, + fold-debounce ==0.2.0.11, + foldl ==1.4.15, + folds ==0.7.8, + follow-file ==0.0.3, + FontyFruity ==0.5.3.5, + force-layout ==0.4.0.6, + foreign-store ==0.2, + ForestStructures ==0.0.1.1, + forkable-monad ==0.2.0.3, + formatn ==0.3.0.1, + format-numbers ==0.1.0.1, + formatting ==7.2.0, + foundation ==0.0.30, + fourmolu ==0.11.0.0, + free ==5.1.10, + free-categories ==0.2.0.2, + freenect ==1.2.1, + freetype2 ==0.2.0, + free-vl ==0.1.4, + friday ==0.2.3.2, + friday-juicypixels ==0.1.2.4, + friendly-time ==0.4.1, + frisby ==0.2.5, + from-sum ==0.2.3.0, + frontmatter ==0.1.0.2, + fsnotify ==0.4.1.0, + ftp-client ==0.5.1.4, + funcmp ==1.9, + function-builder ==0.3.0.1, + functor-classes-compat ==2.0.0.2, + functor-combinators ==0.4.1.2, + fused-effects ==1.1.2.2, + fusion-plugin ==0.2.7, + fusion-plugin-types ==0.1.0, + fuzzcheck ==0.1.1, + fuzzy ==0.1.0.1, + fuzzy-dates ==0.1.1.2, + fuzzy-time ==0.2.0.3, + gauge ==0.2.5, + gd ==3000.7.3, + gdp ==0.0.3.0, + gemini-exports ==0.1.0.0, + general-games ==1.1.1, + generically ==0.1.1, + generic-arbitrary ==1.0.1, + generic-constraints ==1.1.1.1, + generic-data ==1.1.0.0, + generic-data-surgery ==0.3.0.0, + generic-deriving ==1.14.5, + generic-functor ==1.1.0.0, + generic-lens ==2.2.2.0, + generic-lens-core ==2.2.1.0, + generic-monoid ==0.1.0.1, + generic-optics ==2.2.1.0, + GenericPretty ==1.2.2, + generic-random ==1.5.0.1, + generics-eot ==0.4.0.1, + generics-sop ==0.5.1.3, + generics-sop-lens ==0.2.0.1, + geniplate-mirror ==0.7.9, + genvalidity ==1.1.0.0, + genvalidity-aeson ==1.0.0.1, + genvalidity-appendful ==0.1.0.0, + genvalidity-bytestring ==1.0.0.1, + genvalidity-case-insensitive ==0.0.0.1, + genvalidity-containers ==1.0.0.1, + genvalidity-criterion ==1.1.0.0, + genvalidity-hspec ==1.0.0.3, + genvalidity-hspec-aeson ==1.0.0.0, + genvalidity-hspec-binary ==1.0.0.0, + genvalidity-hspec-cereal ==1.0.0.0, + genvalidity-hspec-hashable ==1.0.0.1, + genvalidity-hspec-optics ==1.0.0.0, + genvalidity-hspec-persistent ==1.0.0.0, + genvalidity-mergeful ==0.3.0.1, + genvalidity-mergeless ==0.3.0.0, + genvalidity-persistent ==1.0.0.2, + genvalidity-property ==1.0.0.0, + genvalidity-scientific ==1.0.0.0, + genvalidity-sydtest ==1.0.0.0, + genvalidity-sydtest-aeson ==1.0.0.0, + genvalidity-sydtest-hashable ==1.0.0.1, + genvalidity-sydtest-lens ==1.0.0.0, + genvalidity-sydtest-persistent ==1.0.0.0, + genvalidity-text ==1.0.0.1, + genvalidity-time ==1.0.0.1, + genvalidity-typed-uuid ==0.1.0.1, + genvalidity-unordered-containers ==1.0.0.1, + genvalidity-uuid ==1.0.0.1, + genvalidity-vector ==1.0.0.0, + geodetics ==0.1.2, + getopt-generics ==0.13.1.0, + ghc installed, + ghc-bignum installed, + ghc-byteorder ==4.11.0.0.10, + ghc-check ==0.5.0.8, + ghc-compact installed, + ghc-core ==0.5.6, + ghc-events ==0.19.0.1, + ghc-exactprint ==1.6.1.3, + ghcid ==0.8.9, + ghci-hexcalc ==0.1.1.0, + ghcjs-codemirror ==0.0.0.2, + ghcjs-perch ==0.3.3.3, + ghc-lib ==9.4.8.20231111, + ghc-lib-parser ==9.4.8.20231111, + ghc-lib-parser-ex ==9.4.0.0, + ghc-paths ==0.1.0.12, + ghc-prof ==1.4.1.12, + ghc-syntax-highlighter ==0.0.9.0, + ghc-tcplugins-extra ==0.4.5, + ghc-trace-events ==0.1.2.7, + ghc-typelits-extra ==0.4.6, + ghc-typelits-knownnat ==0.7.10, + ghc-typelits-natnormalise ==0.7.9, + ghc-typelits-presburger ==0.7.2.0, + ghost-buster ==0.1.1.0, + gi-atk ==2.0.27, + gi-cairo ==1.0.29, + gi-cairo-connector ==0.1.1, + gi-cairo-render ==0.1.2, + gi-dbusmenu ==0.4.13, + gi-dbusmenugtk3 ==0.4.14, + gi-freetype2 ==2.0.4, + gi-gdk ==3.0.28, + gi-gdkpixbuf ==2.0.31, + gi-gdkx11 ==3.0.15, + gi-gio ==2.0.32, + gi-glib ==2.0.29, + gi-gmodule ==2.0.5, + gi-gobject ==2.0.30, + gi-graphene ==1.0.7, + gi-gtk ==3.0.41, + gi-gtk-hs ==0.3.16, + gi-harfbuzz ==0.0.9, + gi-javascriptcore ==4.0.27, + gio ==0.13.10.0, + gi-pango ==1.0.29, + gi-soup ==2.4.28, + githash ==0.1.7.0, + github ==0.28.0.1, + github-release ==2.0.0.9, + github-rest ==1.1.4, + github-types ==0.2.1, + github-webhooks ==0.17.0, + gitlab-haskell ==1.0.0.3, + gitlib ==3.1.3, + gitrev ==1.3.1, + gi-vte ==2.91.31, + gi-webkit2 ==4.0.30, + gi-xlib ==2.0.13, + gl ==0.9, + glabrous ==2.0.6.2, + glasso ==0.1.0, + GLFW-b ==3.3.0.0, + glib ==0.13.10.0, + Glob ==0.10.2, + glob-posix ==0.2.0.1, + gloss ==1.13.2.2, + gloss-algorithms ==1.13.0.3, + gloss-rendering ==1.13.1.2, + glpk-headers ==0.5.1, + GLURaw ==2.0.0.5, + GLUT ==2.7.0.16, + gmail-simple ==0.1.0.5, + gnuplot ==0.5.7, + goldplate ==0.2.1.1, + google-isbn ==1.0.3, + gopher-proxy ==0.1.1.3, + gpolyline ==0.1.0.1, + graph-core ==0.3.0.0, + graphite ==0.10.0.1, + graphql ==1.2.0.1, + graphql-client ==1.2.2, + graphs ==0.7.2, + graphula ==2.0.2.2, + graphviz ==2999.20.2.0, + graph-wrapper ==0.2.6.0, + gravatar ==0.8.1, + gridtables ==0.1.0.0, + groom ==0.1.2.1, + group-by-date ==0.1.0.5, + groups ==0.5.3, + gtk ==0.15.8, + gtk2hs-buildtools ==0.13.10.0, + gtk3 ==0.15.8, + gtk-sni-tray ==0.1.8.1, + gtk-strut ==0.1.3.2, + guarded-allocation ==0.0.1, + H ==1.0.0, + hackage-cli ==0.1.0.1, + hackage-db ==2.1.3, + hackage-security ==0.6.2.3, + haddock-library ==1.11.0, + haha ==0.3.1.1, + hakyll ==4.16.2.0, + hal ==1.0.1, + half ==0.3.1, + hall-symbols ==0.1.0.6, + hamlet ==1.2.0, + hamtsolo ==1.0.4, + HandsomeSoup ==0.4.2, + handwriting ==0.1.0.3, + happstack-hsp ==7.3.7.7, + happstack-jmacro ==7.0.12.5, + happstack-server ==7.8.0.2, + happstack-server-tls ==7.2.1.3, + happy ==1.20.1.1, + happy-meta ==0.2.1.0, + harp ==0.4.3.6, + HasBigDecimal ==0.2.0.0, + hasbolt ==0.1.7.0, + hashable ==1.4.3.0, + hashing ==0.1.1.0, + hashmap ==1.3.3, + hashtables ==1.3.1, + haskeline installed, + haskell-gi ==0.26.7, + haskell-gi-base ==0.26.4, + haskell-gi-overloading ==1.0, + haskell-lexer ==1.1.1, + HaskellNet ==0.6.1.2, + HaskellNet-SSL ==0.3.4.4, + haskell-src ==1.0.4, + haskell-src-exts ==1.23.1, + haskell-src-exts-simple ==1.23.0.0, + haskell-src-exts-util ==0.2.5, + haskell-src-meta ==0.8.13, + haskoin-core ==0.21.2, + haskoin-node ==0.18.1, + haskoin-store-data ==0.65.5, + hasktags ==0.72.0, + hasql ==1.6.3.4, + hasql-dynamic-statements ==0.3.1.2, + hasql-implicits ==0.1.1, + hasql-interpolate ==0.1.0.4, + hasql-listen-notify ==0.1.0, + hasql-migration ==0.3.0, + hasql-notifications ==0.2.0.6, + hasql-optparse-applicative ==0.7, + hasql-pool ==0.9.0.1, + hasql-queue ==1.2.0.2, + hasql-th ==0.4.0.19, + hasql-transaction ==1.0.1.2, + has-transformers ==0.1.0.4, + hasty-hamiltonian ==1.3.4, + HaTeX ==3.22.4.1, + HaXml ==1.25.13, + haxr ==3000.11.5, + HCodecs ==0.5.2, + hdaemonize ==0.5.7, + HDBC ==2.4.0.4, + HDBC-session ==0.1.2.1, + headed-megaparsec ==0.2.1.3, + heap ==1.0.4, + heaps ==0.4, + heatshrink ==0.1.0.0, + hebrew-time ==0.1.2, + hedgehog ==1.2, + hedgehog-classes ==0.2.5.4, + hedgehog-corpus ==0.2.0, + hedgehog-fakedata ==0.0.1.5, + hedgehog-fn ==1.0, + hedgehog-optics ==1.0.0.3, + hedgehog-quickcheck ==0.1.1, + hedis ==0.15.2, + hedn ==0.3.0.4, + heist ==1.1.1.2, + here ==1.2.14, + heredoc ==0.2.0.0, + heterocephalus ==1.0.5.7, + hetzner ==0.2.1.1, + hex ==0.2.0, + hexml ==0.3.4, + hexml-lens ==0.2.2, + hexpat ==0.20.13, + hex-text ==0.1.0.9, + hformat ==0.3.3.1, + hfsevents ==0.1.6, + hgal ==2.0.0.3, + hidapi ==0.1.8, + hie-bios ==0.12.1, + hi-file-parser ==0.1.6.0, + highlighting-kate ==0.6.4, + hindent ==6.0.0, + hinfo ==0.0.3.0, + hinotify ==0.4.1, + hint ==0.9.0.8, + histogram-fill ==0.9.1.0, + hjsmin ==0.2.1, + hkd-default ==1.1.0.0, + hkgr ==0.4.3.2, + hledger ==1.30.1, + hledger-interest ==1.6.6, + hledger-lib ==1.30, + hledger-stockquotes ==0.1.2.1, + hledger-ui ==1.30, + hledger-web ==1.30, + hlibcpuid ==0.2.0, + hlibgit2 ==0.18.0.16, + hlibsass ==0.1.10.1, + hlint ==3.5, + hmatrix ==0.20.2, + hmatrix-gsl ==0.19.0.1, + hmatrix-gsl-stats ==0.4.1.8, + hmatrix-morpheus ==0.1.1.2, + hmatrix-special ==0.19.0.0, + hmm-lapack ==0.5.0.1, + hmpfr ==0.4.5, + hoauth2 ==2.8.0, + hoogle ==5.0.18.3, + hopenssl ==2.2.5, + hopfli ==0.2.2.1, + horizontal-rule ==0.6.0.0, + hosc ==0.20, + hostname ==1.0, + hostname-validate ==1.0.0, + hourglass ==0.2.12, + hourglass-orphans ==0.1.0.0, + hp2pretty ==0.10, + hpack ==0.35.2, + hpack-dhall ==0.5.7, + hpc installed, + hpc-codecov ==0.3.0.0, + hpc-lcov ==1.1.1, + HPDF ==1.6.2, + hpp ==0.6.5, + hpqtypes ==1.11.1.2, + hpqtypes-extras ==1.16.4.4, + hreader ==1.1.1, + hreader-lens ==0.1.3.0, + hruby ==0.5.1.0, + hsass ==0.8.0, + hs-bibutils ==6.10.0.0, + hsc2hs ==0.68.10, + hscolour ==1.24.4, + hsdns ==1.8, + hse-cpp ==0.2, + hsemail ==2.2.1, + hset ==2.2.0, + hs-GeoIP ==0.3, + hsignal ==0.2.7.5, + hsini ==0.5.2.2, + hsinstall ==2.8, + HSlippyMap ==3.0.1, + hslogger ==1.3.1.0, + hslua ==2.3.0, + hslua-aeson ==2.3.0.1, + hslua-classes ==2.3.0, + hslua-core ==2.3.1, + hslua-list ==1.1.1, + hslua-marshalling ==2.3.0, + hslua-module-doclayout ==1.1.0, + hslua-module-path ==1.1.0, + hslua-module-system ==1.1.0.1, + hslua-module-text ==1.1.0.1, + hslua-module-version ==1.1.0, + hslua-objectorientation ==2.3.0, + hslua-packaging ==2.3.0, + hslua-typing ==0.1.0, + hsndfile ==0.8.0, + hsndfile-vector ==0.5.2, + HsOpenSSL ==0.11.7.6, + HsOpenSSL-x509-system ==0.1.0.4, + hsp ==0.10.0, + hspec ==2.10.10, + hspec-attoparsec ==0.1.0.2, + hspec-checkers ==0.1.0.2, + hspec-contrib ==0.5.2, + hspec-core ==2.10.10, + hspec-discover ==2.10.10, + hspec-expectations ==0.8.2, + hspec-expectations-json ==1.0.2.1, + hspec-expectations-lifted ==0.10.0, + hspec-expectations-pretty-diff ==0.7.2.6, + hspec-golden ==0.2.1.0, + hspec-golden-aeson ==0.9.0.0, + hspec-hedgehog ==0.0.1.2, + hspec-junit-formatter ==1.1.0.2, + hspec-leancheck ==0.0.6, + hspec-megaparsec ==2.2.1, + hspec-meta ==2.10.5, + hspec-parsec ==0, + hspec-smallcheck ==0.5.3, + hspec-tmp-proc ==0.5.1.2, + hspec-wai ==0.11.1, + hspec-wai-json ==0.11.0, + hspec-webdriver ==1.2.2, + hs-php-session ==0.0.9.3, + hstatistics ==0.3.1, + HStringTemplate ==0.8.8, + HSvm ==0.1.1.3.25, + hsx2hs ==0.14.1.11, + hsx-jmacro ==7.3.8.2, + HsYAML ==0.2.1.3, + HsYAML-aeson ==0.2.0.1, + hsyslog ==5.0.2, + htaglib ==1.2.1, + HTF ==0.15.0.1, + html ==1.0.1.2, + html-conduit ==1.3.2.2, + html-email-validate ==0.2.0.0, + html-entities ==1.1.4.6, + html-entity-map ==0.1.0.0, + htoml-megaparsec ==2.1.0.4, + htoml-parse ==0.1.0.1, + HTTP ==4000.4.1, + http2 ==4.1.4, + http-api-data ==0.5, + http-api-data-qq ==0.1.0.0, + http-client ==0.7.15, + http-client-openssl ==0.3.3, + http-client-overrides ==0.1.1.0, + http-client-restricted ==0.0.5, + http-client-tls ==0.3.6.1, + http-common ==0.8.3.4, + http-conduit ==2.3.8.1, + http-date ==0.0.11, + http-directory ==0.1.10, + http-download ==0.2.0.0, + httpd-shed ==0.4.1.1, + http-io-streams ==0.1.6.3, + http-link-header ==1.2.1, + http-media ==0.8.1.1, + http-query ==0.1.3, + http-reverse-proxy ==0.6.0.2, + http-streams ==0.8.9.9, + http-types ==0.12.4, + human-readable-duration ==0.2.1.4, + HUnit ==1.6.2.0, + HUnit-approx ==1.1.1.1, + hunit-dejafu ==2.0.0.6, + hvect ==0.4.0.1, + hvega ==0.12.0.7, + hw-balancedparens ==0.4.1.3, + hw-bits ==0.7.2.2, + hw-conduit ==0.2.1.1, + hw-conduit-merges ==0.2.1.0, + hw-diagnostics ==0.0.1.0, + hweblib ==0.6.3, + hw-eliasfano ==0.1.2.1, + hw-excess ==0.2.3.0, + hw-fingertree ==0.1.2.1, + hw-fingertree-strict ==0.1.2.1, + hw-hedgehog ==0.1.1.1, + hw-hspec-hedgehog ==0.1.1.1, + hw-int ==0.0.2.0, + hw-ip ==2.4.2.1, + hw-json-simd ==0.1.1.2, + hw-json-simple-cursor ==0.1.1.1, + hw-json-standard-cursor ==0.2.3.2, + hwk ==0.6, + hw-kafka-client ==4.0.3, + hw-mquery ==0.2.1.1, + hworker ==0.1.0.1, + hw-packed-vector ==0.2.1.1, + hw-parser ==0.1.1.0, + hw-prim ==0.6.3.2, + hw-rankselect ==0.13.4.1, + hw-rankselect-base ==0.3.4.1, + hw-simd ==0.1.2.2, + hw-string-parse ==0.0.0.5, + hw-succinct ==0.1.0.1, + hxt ==9.3.1.22, + hxt-charproperties ==9.5.0.0, + hxt-css ==0.1.0.3, + hxt-curl ==9.1.1.1, + hxt-expat ==9.1.1, + hxt-http ==9.1.5.2, + hxt-regex-xmlschema ==9.2.0.7, + hxt-tagsoup ==9.1.4, + hxt-unicode ==9.0.2.4, + hybrid-vectors ==0.2.4, + hyper ==0.2.1.1, + hyperloglog ==0.4.6, + hyphenation ==0.8.2, + identicon ==0.2.2, + ieee754 ==0.8.0, + if ==0.1.0.0, + IfElse ==0.85, + iff ==0.0.6.1, + ihs ==0.1.0.3, + imagesize-conduit ==1.1, + Imlib ==0.1.2, + immortal ==0.3, + immortal-queue ==0.1.0.1, + inbox ==0.2.0, + incipit-base ==0.5.1.0, + incipit-core ==0.5.1.0, + include-file ==0.1.0.4, + incremental ==0.3.1, + indents ==0.5.0.1, + indexed ==0.1.3, + indexed-containers ==0.1.0.2, + indexed-list-literals ==0.2.1.3, + indexed-profunctors ==0.1.1.1, + indexed-traversable ==0.1.3, + indexed-traversable-instances ==0.1.1.2, + inf-backprop ==0.1.0.2, + infer-license ==0.2.0, + infinite-list ==0.1, + ini ==0.4.2, + inj ==1.0, + inline-c ==0.9.1.10, + inline-c-cpp ==0.5.0.2, + inline-r ==1.0.1, + input-parsers ==0.3.0.2, + insert-ordered-containers ==0.2.5.3, + inspection-testing ==0.5.0.2, + instance-control ==0.1.2.0, + integer-gmp installed, + integer-logarithms ==1.0.3.1, + integer-roots ==1.0.2.0, + integer-types ==0.1.4.0, + integration ==0.2.1, + intern ==0.9.5, + interpolate ==0.2.1, + interpolatedstring-perl6 ==1.0.2, + interpolation ==0.1.1.2, + Interpolation ==0.3.0, + IntervalMap ==0.6.2.1, + intervals ==0.9.2, + intset-imperative ==0.1.0.0, + invariant ==0.6.2, + invert ==1.0.0.4, + invertible-grammar ==0.1.3.5, + io-machine ==0.2.0.0, + io-manager ==0.1.0.4, + io-memoize ==1.1.1.0, + io-region ==0.1.1, + io-storage ==0.3, + io-streams ==1.5.2.2, + io-streams-haproxy ==1.0.1.0, + ip ==1.7.7, + ip6addr ==1.0.3, + iproute ==1.7.12, + IPv6Addr ==2.0.5.1, + ipynb ==0.2, + ipython-kernel ==0.10.3.0, + irc ==0.6.1.1, + irc-ctcp ==0.1.3.1, + isbn ==1.1.0.4, + islink ==0.1.0.0, + iso3166-country-codes ==0.20140203.8, + iso639 ==0.1.0.3, + iso8601-time ==0.1.5, + isocline ==1.0.9, + isomorphism-class ==0.1.0.12, + iterable ==3.0, + ix-shapable ==0.1.0, + jack ==0.7.2.2, + jailbreak-cabal ==1.4, + jalaali ==1.0.0.0, + java-adt ==0.2018.11.4, + jira-wiki-markup ==1.5.1, + jl ==0.1.0, + jmacro ==0.6.18, + jose ==0.10.0.1, + jose-jwt ==0.9.6, + journalctl-stream ==0.6.0.5, + js-chart ==2.9.4.1, + js-dgtable ==0.5.2, + js-flot ==0.8.3, + js-jquery ==3.3.1, + json ==0.10, + json-feed ==2.0.0.10, + jsonifier ==0.2.1.2, + jsonpath ==0.3.0.0, + json-rpc ==1.0.4, + json-stream ==0.4.5.3, + JuicyPixels ==3.3.8, + JuicyPixels-extra ==0.6.0, + JuicyPixels-scale-dct ==0.1.2, + junit-xml ==0.1.0.3, + justified-containers ==0.3.0.0, + jwt ==0.11.0, + kan-extensions ==5.2.5, + kansas-comet ==0.4.2, + katip ==0.8.8.0, + katip-logstash ==0.1.0.2, + katip-wai ==0.1.2.2, + kazura-queue ==0.1.0.4, + kdt ==0.2.5, + keep-alive ==0.2.1.0, + keter ==2.1.2, + keycode ==0.2.2, + keyed-vals ==0.2.2.0, + keyed-vals-hspec-tests ==0.2.2.0, + keyed-vals-mem ==0.2.2.0, + keyed-vals-redis ==0.2.2.0, + keys ==3.12.3, + ki ==1.0.1.1, + kind-apply ==0.4.0.0, + kind-generics ==0.5.0.0, + kind-generics-th ==0.2.3.3, + ki-unlifted ==1.0.0.2, + kleene ==0.1, + kmeans ==0.1.3, + knob ==0.2.2, + koji ==0.0.2, + krank ==0.3.0, + labels ==0.3.3, + lackey ==2.0.0.7, + LambdaHack ==0.11.0.1, + lame ==0.2.2, + language-avro ==0.1.4.0, + language-bash ==0.9.2, + language-c ==0.9.2, + language-c-quote ==0.13.0.1, + language-docker ==12.1.0, + language-dot ==0.1.2, + language-glsl ==0.3.0, + language-java ==0.2.9, + language-javascript ==0.7.1.0, + language-nix ==2.2.0, + language-protobuf ==1.0.1, + language-python ==0.5.8, + language-thrift ==0.12.0.1, + lapack ==0.5.1, + lapack-carray ==0.0.3, + lapack-comfort-array ==0.0.1, + lapack-ffi ==0.0.3, + lapack-ffi-tools ==0.1.3.1, + lapack-hmatrix ==0.0.0.2, + largeword ==1.2.5, + latex ==0.1.0.4, + lattices ==2.1, + lawful ==0.1.0.0, + lazy-csv ==0.5.1, + lazyio ==0.1.0.4, + lazysmallcheck ==0.6, + lca ==0.4, + leancheck ==1.0.0, + leancheck-instances ==0.0.5, + leapseconds-announced ==2017.1.0.1, + learn-physics ==0.6.5, + leb128-cereal ==1.2, + lens ==5.2.3, + lens-action ==0.2.6, + lens-aeson ==1.2.3, + lens-csv ==0.1.1.0, + lens-family ==2.1.2, + lens-family-core ==2.1.2, + lens-misc ==0.0.2.0, + lens-properties ==4.11.1, + lens-regex ==0.1.3, + lens-regex-pcre ==1.1.0.0, + lentil ==1.5.6.0, + LetsBeRational ==1.0.0.0, + leveldb-haskell ==0.6.5, + lexer-applicative ==2.1.0.2, + libBF ==0.6.7, + libffi ==0.2.1, + libgit ==0.3.1, + liboath-hs ==0.0.1.2, + libyaml ==0.1.2, + lifted-async ==0.10.2.5, + lifted-base ==0.2.3.12, + lift-generics ==0.2.1, + lift-type ==0.1.1.1, + line ==4.0.1, + linear ==1.22, + linear-base ==0.3.1, + linear-circuit ==0.1.0.4, + linear-generics ==0.2.1, + linear-programming ==0.0.0.1, + linebreak ==1.1.0.4, + linux-capabilities ==0.1.1.0, + linux-file-extents ==0.2.0.0, + linux-namespaces ==0.1.3.0, + List ==0.6.2, + ListLike ==4.7.8.2, + list-predicate ==0.1.0.1, + listsafe ==0.1.0.1, + list-t ==1.0.5.7, + list-transformer ==1.0.9, + ListTree ==0.2.3, + ListZipper ==1.2.0.2, + literatex ==0.3.0.0, + lmdb ==0.2.5, + load-env ==0.2.1.0, + loc ==0.1.4.1, + locators ==0.3.0.3, + loch-th ==0.2.2, + lockfree-queue ==0.2.4, + log-base ==0.12.0.1, + log-domain ==0.13.2, + logfloat ==0.14.0, + logger-thread ==0.1.0.2, + logging ==3.0.5, + logging-effect ==1.4.0, + logging-facade ==0.3.1, + logging-facade-syslog ==1, + logict ==0.8.0.0, + logstash ==0.1.0.4, + loop ==0.3.0, + lpeg ==1.0.4, + lrucache ==1.2.0.1, + lsp ==2.0.0.0, + lsp-test ==0.15.0.0, + lsp-types ==2.0.2.0, + lua ==2.3.1, + lua-arbitrary ==1.0.1.1, + lucid ==2.11.20230408, + lucid2 ==0.0.20230706, + lucid-cdn ==0.2.2.0, + lucid-extras ==0.2.2, + lukko ==0.1.1.3, + lz4 ==0.2.3.1, + lz4-frame-conduit ==0.1.0.1, + lzma ==0.0.1.0, + lzma-clib ==5.2.2, + lzma-conduit ==1.2.3, + machines ==0.7.3, + magic ==1.1, + magico ==0.0.2.3, + mail-pool ==2.2.3, + mainland-pretty ==0.7.1, + main-tester ==0.2.0.1, + managed ==1.0.10, + mandrill ==0.5.7.0, + map-syntax ==0.3, + markdown ==0.1.17.5, + markdown-unlit ==0.5.1, + markov-chain ==0.0.3.4, + markov-chain-usage-model ==0.0.0, + mason ==0.2.6, + massiv ==1.0.4.0, + massiv-io ==1.0.0.1, + massiv-serialise ==1.0.0.2, + massiv-test ==1.0.0.0, + matchable ==0.1.2.1, + mathexpr ==0.3.1.0, + math-extras ==0.1.1.0, + math-functions ==0.3.4.3, + mathlist ==0.2.0.0, + matplotlib ==0.7.7, + matrices ==0.5.0, + matrix ==0.3.6.3, + matrix-as-xyz ==0.1.2.2, + matrix-market-attoparsec ==0.1.1.3, + matrix-static ==0.3, + maximal-cliques ==0.1.1, + mbox-utility ==0.0.3.1, + mcmc ==0.8.2.0, + mcmc-types ==1.0.3, + median-stream ==0.7.0.0, + med-module ==0.1.3, + megaparsec ==9.3.1, + megaparsec-tests ==9.3.1, + mega-sdist ==0.4.3.0, + membership ==0.0.1, + memcache ==0.3.0.1, + memfd ==1.0.1.3, + memory ==0.18.0, + MemoTrie ==0.6.11, + mergeful ==0.3.0.0, + mergeless ==0.4.0.0, + merkle-tree ==0.1.1, + mersenne-random ==1.0.0.1, + mersenne-random-pure64 ==0.2.2.0, + messagepack ==0.5.5, + metrics ==0.4.1.1, + mfsolve ==0.3.2.2, + microaeson ==0.1.0.1, + microlens ==0.4.13.1, + microlens-aeson ==2.5.1, + microlens-contra ==0.1.0.3, + microlens-ghc ==0.4.14.2, + microlens-mtl ==0.2.0.3, + microlens-platform ==0.4.3.4, + microlens-th ==0.4.3.14, + microspec ==0.2.1.3, + microstache ==1.0.2.3, + midair ==0.2.0.1, + midi ==0.2.2.4, + midi-alsa ==0.2.1, + midi-music-box ==0.0.1.2, + mighty-metropolis ==2.0.0, + mime-mail ==0.5.1, + mime-mail-ses ==0.4.3, + mime-types ==0.1.2.0, + minimal-configuration ==0.1.4, + minimorph ==0.3.0.1, + minio-hs ==1.7.0, + minisat-solver ==0.1, + miniutter ==0.5.1.2, + min-max-pqueue ==0.1.0.2, + mintty ==0.1.4, + misfortune ==0.1.2.1, + missing-foreign ==0.1.1, + MissingH ==1.6.0.1, + mixed-types-num ==0.5.12, + mmap ==0.5.9, + mmark ==0.0.7.6, + mmark-cli ==0.0.5.1, + mmark-ext ==0.2.1.5, + mmorph ==1.2.0, + mnist-idx ==0.1.3.2, + mnist-idx-conduit ==0.4.0.0, + mockery ==0.3.5, + mock-time ==0.1.0, + mod ==0.2.0.1, + model ==0.5, + modern-uri ==0.3.6.1, + modular ==0.1.0.8, + monad-chronicle ==1.0.1, + monad-control ==1.0.3.1, + monad-control-identity ==0.2.0.0, + monad-coroutine ==0.9.2, + monad-extras ==0.6.0, + monadic-arrays ==0.2.2, + monad-journal ==0.8.1, + monadlist ==0.0.2, + monadloc ==0.7.1, + monad-logger ==0.3.40, + monad-logger-aeson ==0.4.1.2, + monad-logger-json ==0.1.0.0, + monad-logger-logstash ==0.2.0.2, + monad-loops ==0.4.3, + monad-memo ==0.5.4, + monadoid ==0.0.3, + monadology ==0.1, + monad-par ==0.3.6, + monad-parallel ==0.8, + monad-par-extras ==0.3.3, + monad-peel ==0.2.1.2, + monad-primitive ==0.1, + monad-products ==4.0.1, + MonadPrompt ==1.0.0.5, + MonadRandom ==0.6, + monad-resumption ==0.1.4.0, + monad-st ==0.2.4.1, + monads-tf ==0.1.0.3, + monad-time ==0.4.0.0, + mongoDB ==2.7.1.2, + monoidal-containers ==0.6.4.0, + monoid-extras ==0.6.2, + monoid-subclasses ==1.2.4.1, + monoid-transformer ==0.0.4, + mono-traversable ==1.0.15.3, + mono-traversable-instances ==0.1.1.0, + mono-traversable-keys ==0.3.0, + more-containers ==0.2.2.2, + morpheus-graphql ==0.27.3, + morpheus-graphql-app ==0.27.3, + morpheus-graphql-client ==0.27.3, + morpheus-graphql-code-gen ==0.27.3, + morpheus-graphql-code-gen-utils ==0.27.3, + morpheus-graphql-core ==0.27.3, + morpheus-graphql-server ==0.27.3, + morpheus-graphql-subscriptions ==0.27.3, + morpheus-graphql-tests ==0.27.3, + moss ==0.2.0.1, + mountpoints ==1.0.2, + mpi-hs ==0.7.2.0, + mpi-hs-binary ==0.1.1.0, + mpi-hs-cereal ==0.1.0.0, + mstate ==0.2.8, + mtl installed, + mtl-compat ==0.2.2, + mtl-prelude ==2.0.3.2, + multiarg ==0.30.0.10, + multi-containers ==0.2, + multimap ==1.2.1, + multipart ==0.2.1, + MultipletCombiner ==0.0.7, + multiset ==0.3.4.3, + murmur3 ==1.0.5, + murmur-hash ==0.1.0.10, + MusicBrainz ==0.4.1, + mustache ==2.4.2, + mutable-containers ==0.3.4.1, + mwc-probability ==2.3.1, + mwc-random ==0.15.0.2, + mwc-random-monad ==0.7.3.1, + mx-state-codes ==1.0.0.0, + mysql ==0.2.1, + mysql-simple ==0.4.9, + n2o ==0.11.1, + n2o-nitro ==0.11.2, + nagios-check ==0.3.2, + named ==0.3.0.1, + names-th ==0.3.0.1, + nano-erl ==0.1.0.1, + nanospec ==0.2.2, + nanovg ==0.8.1.0, + nats ==1.1.2, + natural-arithmetic ==0.1.4.0, + natural-induction ==0.2.0.0, + natural-sort ==0.1.2, + natural-transformation ==0.4, + ndjson-conduit ==0.1.0.5, + neat-interpolation ==0.5.1.4, + netcode-io ==0.0.3, + netlib-carray ==0.1, + netlib-comfort-array ==0.0.0.2, + netlib-ffi ==0.1.1, + net-mqtt ==0.8.3.0, + net-mqtt-lens ==0.1.1.0, + netpbm ==1.0.4, + netrc ==0.2.0.0, + nettle ==0.3.0, + netwire ==5.0.3, + netwire-input ==0.0.7, + netwire-input-glfw ==0.0.11, + network ==3.1.4.0, + network-bsd ==2.8.1.0, + network-byte-order ==0.1.7, + network-conduit-tls ==1.3.2, + network-info ==0.2.1, + network-ip ==0.3.0.3, + network-messagepack-rpc ==0.1.2.0, + network-messagepack-rpc-websocket ==0.1.1.1, + network-multicast ==0.3.2, + Network-NineP ==0.4.7.3, + network-run ==0.2.6, + network-simple ==0.4.5, + network-simple-tls ==0.4.1, + network-transport ==0.5.6, + network-uri ==2.6.4.2, + network-wait ==0.2.0.0, + newtype ==0.2.2.0, + newtype-generics ==0.6.2, + nfc ==0.1.1, + nicify-lib ==1.0.1, + NineP ==0.0.2.1, + nix-derivation ==1.1.3, + nix-paths ==1.0.1, + NoHoed ==0.1.1, + nonce ==1.0.7, + nondeterminism ==1.5, + non-empty ==0.3.5, + nonempty-containers ==0.3.4.5, + nonemptymap ==0.0.6.0, + non-empty-sequence ==0.2.0.4, + nonempty-vector ==0.2.3, + nonempty-zipper ==1.0.0.4, + non-negative ==0.1.2, + normaldistribution ==1.1.0.3, + not-gloss ==0.7.7.0, + nothunks ==0.1.5, + no-value ==1.0.0.0, + nowdoc ==0.1.1.0, + nqe ==0.6.5, + nsis ==0.3.3, + numbers ==3000.2.0.2, + numeric-extras ==0.1, + numeric-limits ==0.1.0.0, + numeric-prelude ==0.4.4, + numeric-quest ==0.2.0.2, + numhask ==0.10.1.1, + numhask-array ==0.10.2, + NumInstances ==1.4, + numtype-dk ==0.5.0.3, + nuxeo ==0.3.2, + nvim-hs ==2.3.2.3, + nvim-hs-contrib ==2.0.0.2, + nvim-hs-ghcid ==2.0.1.0, + oauthenticated ==0.3.0.0, + ObjectName ==1.1.0.2, + oblivious-transfer ==0.1.0, + o-clock ==1.3.0, + ofx ==0.4.4.0, + oidc-client ==0.7.0.1, + old-locale ==1.0.0.7, + old-time ==1.1.0.4, + once ==0.4, + one-liner ==2.1, + one-liner-instances ==0.1.3.0, + OneTuple ==0.4.1.1, + Only ==0.1, + oo-prototypes ==0.1.0.0, + oops ==0.2.0.1, + opaleye ==0.9.7.0, + OpenAL ==1.7.0.5, + openapi3 ==3.2.4, + open-browser ==0.2.1.0, + openexr-write ==0.1.0.2, + OpenGL ==3.0.3.0, + OpenGLRaw ==3.3.4.1, + openpgp-asciiarmor ==0.1.2, + opensource ==0.1.1.0, + openssl-streams ==1.2.3.0, + opentelemetry ==0.8.0, + opentelemetry-extra ==0.8.0, + opentelemetry-lightstep ==0.8.0, + opentelemetry-wai ==0.8.0, + open-witness ==0.6, + operational ==0.2.4.2, + operational-class ==0.3.0.0, + opml-conduit ==0.9.0.0, + optics ==0.4.2.1, + optics-core ==0.4.1.1, + optics-extra ==0.4.2.1, + optics-operators ==0.1.0.1, + optics-th ==0.4.1, + optics-vl ==0.2.1, + optima ==0.4.0.5, + optional-args ==1.0.2, + options ==1.2.1.1, + optparse-applicative ==0.17.1.0, + optparse-enum ==1.0.0.0, + optparse-generic ==1.4.9, + optparse-simple ==0.1.1.4, + optparse-text ==0.1.1.0, + OrderedBits ==0.0.2.0, + ordered-containers ==0.2.3, + ormolu ==0.5.3.0, + overhang ==1.0.0, + packcheck ==0.6.0, + pager ==0.1.1.0, + pagination ==0.2.2, + pagure ==0.1.1, + pagure-cli ==0.2.1, + palette ==0.3.0.3, + pandoc ==3.0.1, + pandoc-dhall-decoder ==0.1.0.1, + pandoc-lua-marshal ==0.2.2, + pandoc-plot ==1.7.0, + pandoc-symreg ==0.2.0.0, + pandoc-throw ==0.1.0.0, + pandoc-types ==1.23.1, + pango ==0.13.10.0, + pantry ==0.8.3, + parallel ==3.2.2.0, + parallel-io ==0.3.5, + parameterized ==0.5.0.0, + parseargs ==0.2.0.9, + parsec installed, + parsec-class ==1.0.0.0, + parsec-numbers ==0.1.0, + parsec-numeric ==0.1.0.0, + ParsecTools ==0.0.2.0, + parser-combinators ==1.3.0, + parser-combinators-tests ==1.3.0, + parsers ==0.12.11, + partial-handler ==1.0.3, + partial-isomorphisms ==0.2.3.0, + partial-order ==0.2.0.0, + partial-semigroup ==0.6.0.2, + password ==3.0.2.1, + password-instances ==3.0.0.0, + password-types ==1.0.0.0, + path ==0.9.5, + path-binary-instance ==0.1.0.1, + path-dhall-instance ==0.2.1.0, + path-extensions ==0.1.1.0, + path-extra ==0.2.0, + path-io ==1.8.1, + path-like ==0.2.0.2, + path-pieces ==0.2.1, + path-text-utf8 ==0.0.1.12, + pathtype ==0.8.1.2, + path-utils ==0.1.1.0, + pathwalk ==0.3.1.2, + patrol ==1.0.0.6, + pattern-arrows ==0.0.2, + pava ==0.1.1.4, + pcf-font ==0.2.2.1, + pcg-random ==0.1.4.0, + pcre2 ==2.2.1, + pcre-heavy ==1.0.0.3, + pcre-light ==0.4.1.2, + pcre-utils ==0.1.9, + pdc ==0.1.1, + pdf-toolbox-content ==0.1.1, + pdf-toolbox-core ==0.1.1, + pdf-toolbox-document ==0.1.2, + peano ==0.1.0.2, + pedersen-commitment ==0.2.0, + pem ==0.2.4, + percent-format ==0.0.4, + perfect-hash-generator ==1.0.0, + persistent ==2.14.6.0, + persistent-discover ==0.1.0.7, + persistent-documentation ==0.1.0.4, + persistent-iproute ==0.2.5, + persistent-lens ==1.0.0, + persistent-mongoDB ==2.13.0.1, + persistent-mtl ==0.5.0.1, + persistent-mysql ==2.13.1.5, + persistent-pagination ==0.1.1.2, + persistent-postgresql ==2.13.6.1, + persistent-qq ==2.12.0.6, + persistent-redis ==2.13.0.1, + persistent-refs ==0.4, + persistent-sqlite ==2.13.3.0, + persistent-template ==2.12.0.0, + persistent-test ==2.13.1.3, + persistent-typed-db ==0.1.0.7, + pg-harness-client ==0.6.0, + pgp-wordlist ==0.1.0.3, + pg-transact ==0.3.2.0, + phantom-state ==0.2.1.4, + phatsort ==0.6.0.0, + picosat ==0.1.6, + pid1 ==0.1.3.1, + pinch ==0.4.3.0, + pipes ==4.3.16, + pipes-attoparsec ==0.6.0, + pipes-bytestring ==2.1.7, + pipes-concurrency ==2.0.14, + pipes-csv ==1.4.3, + pipes-extras ==1.0.15, + pipes-fastx ==0.3.0.0, + pipes-fluid ==0.6.0.1, + pipes-group ==1.0.12, + pipes-http ==1.0.6, + pipes-mongodb ==0.1.0.0, + pipes-ordered-zip ==1.2.1, + pipes-parse ==3.0.9, + pipes-random ==1.0.0.5, + pipes-safe ==2.3.5, + pipes-text ==1.0.1, + pipes-wai ==3.2.0, + pkgtreediff ==0.6.0, + place-cursor-at ==1.0.1, + placeholders ==0.1, + plaid ==0.1.0.4, + plot ==0.2.3.11, + plotlyhs ==0.2.3, + Plural ==0.0.2, + pointed ==5.0.4, + pointedlist ==0.6.1, + pointless-fun ==1.1.0.8, + poll ==0.0.0.2, + poly-arity ==0.1.0, + polynomials-bernstein ==1.1.2, + polyparse ==1.13, + polysemy ==1.9.1.3, + polysemy-fs ==0.1.0.0, + polysemy-plugin ==0.4.5.1, + polysemy-webserver ==0.2.1.2, + pontarius-xmpp ==0.5.6.6, + pooled-io ==0.0.2.3, + portable-lines ==0.1, + port-utils ==0.2.1.0, + posix-paths ==0.3.0.0, + posix-pty ==0.2.2, + possibly ==1.0.0.0, + postgres-options ==0.2.1.0, + postgresql-binary ==0.13.1.2, + postgresql-libpq ==0.9.5.0, + postgresql-libpq-notify ==0.2.0.0, + postgresql-migration ==0.2.1.7, + postgresql-schema ==0.1.14, + postgresql-simple ==0.6.5.1, + postgresql-simple-url ==0.2.1.0, + postgresql-syntax ==0.4.1.1, + postgresql-typed ==0.6.2.2, + post-mess-age ==0.2.1.0, + pptable ==0.3.0.0, + pqueue ==1.4.3.0, + prairie ==0.0.2.0, + prefix-units ==0.3.0.1, + prelude-compat ==0.0.0.2, + prelude-safeenum ==0.1.1.3, + pretty installed, + pretty-class ==1.0.1.1, + prettyclass ==1.0.0.0, + pretty-hex ==1.1, + prettyprinter ==1.7.1, + prettyprinter-ansi-terminal ==1.1.3, + prettyprinter-combinators ==0.1.2, + prettyprinter-compat-annotated-wl-pprint ==1.1, + prettyprinter-compat-ansi-wl-pprint ==1.0.2, + prettyprinter-compat-wl-pprint ==1.0.1, + prettyprinter-convert-ansi-wl-pprint ==1.1.2, + pretty-relative-time ==0.3.0.0, + pretty-show ==1.10, + pretty-simple ==4.1.2.0, + pretty-sop ==0.2.0.3, + pretty-terminal ==0.1.0.0, + pretty-types ==0.4.0.0, + primes ==0.2.1.0, + primitive ==0.8.0.0, + primitive-addr ==0.1.0.2, + primitive-extras ==0.10.1.10, + primitive-offset ==0.2.0.0, + primitive-unaligned ==0.1.1.2, + primitive-unlifted ==0.1.3.1, + prim-uniq ==0.2, + print-console-colors ==0.1.0.0, + probability ==0.2.8, + process installed, + process-extras ==0.7.4, + product-profunctors ==0.11.1.1, + profiterole ==0.1, + profunctors ==5.6.2, + projectroot ==0.2.0.1, + project-template ==0.2.1.0, + prometheus-client ==1.1.1, + prometheus-metrics-ghc ==1.0.1.2, + promises ==0.3, + prompt ==0.1.1.2, + prospect ==0.1.0.0, + protobuf ==0.2.1.3, + protobuf-simple ==0.1.1.1, + protocol-radius ==0.0.1.1, + protocol-radius-test ==0.1.0.1, + proto-lens ==0.7.1.3, + proto-lens-optparse ==0.1.1.10, + proto-lens-runtime ==0.7.0.4, + protolude ==0.3.3, + proxied ==0.3.1, + psql-helpers ==0.1.0.0, + PSQueue ==1.2.0, + psqueues ==0.2.8.0, + pthread ==0.2.1, + ptr ==0.16.8.5, + ptr-poker ==0.1.2.14, + pulse-simple ==0.1.14, + pureMD5 ==2.1.4, + purescript-bridge ==0.15.0.0, + pusher-http-haskell ==2.1.0.17, + pvar ==1.0.0.0, + pwstore-fast ==2.4.4, + PyF ==0.11.2.1, + qchas ==1.1.0.1, + qm-interpolated-string ==0.3.1.0, + qrcode-core ==0.9.9, + qrcode-juicypixels ==0.8.5, + quaalude ==0.0.0.1, + quadratic-irrational ==0.1.1, + QuasiText ==0.1.2.6, + QuickCheck ==2.14.3, + quickcheck-arbitrary-adt ==0.3.1.0, + quickcheck-assertions ==0.3.0, + quickcheck-classes ==0.6.5.0, + quickcheck-classes-base ==0.6.2.0, + quickcheck-groups ==0.0.0.0, + quickcheck-higherorder ==0.1.0.1, + quickcheck-instances ==0.3.30, + quickcheck-io ==0.2.0, + quickcheck-monoid-subclasses ==0.1.0.0, + quickcheck-simple ==0.1.1.1, + quickcheck-special ==0.1.0.6, + quickcheck-state-machine ==0.7.3, + quickcheck-text ==0.1.2.1, + quickcheck-transformer ==0.3.1.2, + quickcheck-unicode ==1.0.1.0, + quicklz ==1.5.0.11, + quiet ==0.2, + quote-quot ==0.2.1.0, + radius ==0.7.1.0, + rainbow ==0.34.2.2, + rainbox ==0.26.0.0, + ral ==0.2.1, + rampart ==2.0.0.7, + ramus ==0.1.2, + rando ==0.0.0.4, + random ==1.2.1.1, + random-bytestring ==0.1.4, + random-fu ==0.3.0.1, + random-shuffle ==0.0.4, + random-tree ==0.6.0.5, + range ==0.3.0.2, + ranged-list ==0.1.2.1, + Ranged-sets ==0.4.0, + ranges ==0.2.4, + range-set-list ==0.1.3.1, + rank1dynamic ==0.4.1, + Rasterific ==0.7.5.4, + rasterific-svg ==0.3.3.2, + ratel ==2.0.0.10, + rate-limit ==1.4.3, + ratel-wai ==2.0.0.5, + ratio-int ==0.1.2, + rattle ==0.2, + rattletrap ==12.0.3, + Rattus ==0.5.1.1, + rawfilepath ==1.0.1, + rawstring-qm ==0.2.3.0, + raw-strings-qq ==1.1, + rcu ==0.2.7, + rdtsc ==1.3.0.1, + re2 ==0.3, + reactive-balsa ==0.4.0.1, + reactive-banana ==1.3.2.0, + reactive-banana-bunch ==1.0.0.1, + reactive-jack ==0.4.1.2, + reactive-midyim ==0.4.1.1, + readable ==0.3.1, + read-editor ==0.1.0.2, + read-env-var ==1.0.0.0, + rebase ==1.19, + rec-def ==0.2.2, + record-dot-preprocessor ==0.2.16, + record-hasfield ==1.0, + recursion-schemes ==5.2.2.5, + recv ==0.1.0, + redact ==0.5.0.0, + reddit-scrape ==0.0.1, + redis-glob ==0.1.0.6, + reducers ==3.12.4, + refact ==0.3.0.2, + ref-fd ==0.5.0.1, + refined ==0.8.1, + refinery ==0.4.0.0, + reflection ==2.1.7, + reform ==0.2.7.5, + reform-blaze ==0.2.4.4, + reform-happstack ==0.2.5.6, + RefSerialize ==0.4.0, + ref-tf ==0.5.0.1, + regex ==1.1.0.2, + regex-applicative ==0.3.4, + regex-applicative-text ==0.1.0.1, + regex-base ==0.94.0.2, + regex-compat ==0.95.2.1, + regex-pcre ==0.95.0.0, + regex-pcre-builtin ==0.95.2.3.8.44, + regex-posix ==0.96.0.1, + regex-posix-clib ==2.7, + regex-tdfa ==1.3.2.2, + regex-with-pcre ==1.1.0.2, + reinterpret-cast ==0.1.0, + rel8 ==1.4.1.0, + relapse ==1.0.0.1, + reliable-io ==0.0.2, + relude ==1.2.1.0, + renderable ==0.2.0.1, + replace-attoparsec ==1.5.0.0, + replace-megaparsec ==1.5.0.1, + repline ==0.4.2.0, + req ==3.13.0, + req-conduit ==1.0.1, + rerebase ==1.19, + reroute ==0.7.0.0, + resistor-cube ==0.0.1.4, + resolv ==0.2.0.2, + resource-pool ==0.4.0.0, + resourcet ==1.2.6, + rest-rewrite ==0.4.2, + result ==0.2.6.0, + retry ==0.9.3.1, + rev-state ==0.1.2, + rex ==0.6.2, + rfc1751 ==0.1.3, + rfc5051 ==0.2, + rg ==1.4.0.0, + rhbzquery ==0.4.4, + riak-protobuf ==0.25.0.0, + rio ==0.1.22.0, + rio-orphans ==0.1.2.0, + rio-prettyprint ==0.1.7.0, + rng-utils ==0.3.1, + rocksdb-haskell ==1.0.1, + rocksdb-haskell-jprupp ==2.1.6, + rocksdb-query ==0.4.2, + roles ==0.2.1.0, + rollbar ==1.1.3, + rope-utf16-splay ==0.4.0.0, + rosezipper ==0.2, + rot13 ==0.2.0.1, + row-types ==1.0.1.2, + rpmbuild-order ==0.4.10, + rpm-nvr ==0.1.2, + rp-tree ==0.7.1, + rrb-vector ==0.2.1.0, + RSA ==2.4.1, + rss ==3000.2.0.7, + rss-conduit ==0.6.0.1, + run-haskell-module ==0.0.2, + runmemo ==1.0.0.1, + run-st ==0.1.3.0, + rvar ==0.3.0.2, + s3-signer ==0.5.0.0, + safe ==0.3.19, + safe-coloured-text ==0.2.0.1, + safe-coloured-text-gen ==0.0.0.2, + safe-coloured-text-layout ==0.0.0.0, + safe-coloured-text-layout-gen ==0.0.0.0, + safe-coloured-text-terminfo ==0.1.0.0, + safecopy ==0.10.4.2, + safe-decimal ==0.2.1.0, + safe-exceptions ==0.1.7.4, + safe-exceptions-checked ==0.1.0, + safe-foldable ==0.1.0.0, + safe-gen ==1.0.1, + safeio ==0.0.6.0, + safe-json ==1.1.4.0, + safe-money ==0.9.1, + SafeSemaphore ==0.10.1, + saltine ==0.2.1.0, + salve ==2.0.0.4, + sample-frame ==0.0.4, + sample-frame-np ==0.0.5, + sampling ==0.3.5, + sandi ==0.5, + sandwich ==0.1.5.2, + sandwich-hedgehog ==0.1.3.0, + sandwich-quickcheck ==0.1.0.7, + sandwich-slack ==0.1.2.0, + sandwich-webdriver ==0.2.3.1, + say ==0.1.0.1, + sbp ==4.15.0, + sbv ==10.2, + scalpel ==0.6.2.2, + scalpel-core ==0.6.2.2, + scanf ==0.1.0.0, + scanner ==0.3.1, + scheduler ==2.0.0.1, + SciBaseTypes ==0.1.1.0, + scientific ==0.3.7.0, + scientist ==0.0.0.0, + scotty ==0.12.1, + scrypt ==0.5.0, + sdl2 ==2.5.5.0, + sdl2-gfx ==0.3.0.0, + sdl2-image ==2.1.0.0, + sdl2-mixer ==1.2.0.0, + sdl2-ttf ==2.1.3, + search-algorithms ==0.3.2, + secp256k1-haskell ==0.6.1, + securemem ==0.1.10, + selections ==0.3.0.0, + selective ==0.7, + semialign ==1.3, + semigroupoid-extras ==5, + semigroupoids ==5.3.7, + semigroups ==0.20, + semirings ==0.6, + semiring-simple ==1.0.0.1, + semver ==0.4.0.1, + sendfile ==0.7.11.5, + sendgrid-v3 ==1.0.0.1, + seqalign ==0.2.0.4, + seqid ==0.6.3, + seqid-streams ==0.7.2, + sequence-formats ==1.7.1, + sequenceTools ==1.5.3.1, + serialise ==0.2.6.1, + servant ==0.19.1, + servant-auth ==0.4.1.0, + servant-auth-client ==0.4.1.1, + servant-auth-docs ==0.2.10.0, + servant-auth-wordpress ==1.0.0.2, + servant-blaze ==0.9.1, + servant-cassava ==0.10.2, + servant-checked-exceptions ==2.2.0.1, + servant-checked-exceptions-core ==2.2.0.1, + servant-client ==0.19, + servant-client-core ==0.19, + servant-conduit ==0.15.1, + servant-docs ==0.12, + servant-elm ==0.7.3, + servant-exceptions ==0.2.1, + servant-exceptions-server ==0.2.1, + servant-foreign ==0.15.4, + servant-http-streams ==0.18.4, + servant-lucid ==0.9.0.6, + servant-machines ==0.15.1, + servant-multipart ==0.12.1, + servant-multipart-api ==0.12.1, + servant-multipart-client ==0.12.2, + servant-openapi3 ==2.0.1.6, + servant-pipes ==0.15.3, + servant-rate-limit ==0.2.0.0, + servant-rawm ==1.0.0.0, + servant-server ==0.19.2, + servant-static-th ==1.0.0.0, + servant-subscriber ==0.7.0.0, + servant-swagger ==1.1.11, + servant-swagger-ui ==0.3.5.5.0.0, + servant-swagger-ui-core ==0.3.5, + servant-websockets ==2.0.0, + servant-xml ==1.0.2, + serversession ==1.0.3, + serversession-backend-redis ==1.0.5, + serversession-frontend-wai ==1.0.1, + serversession-frontend-yesod ==1.0.1, + servius ==1.2.3.0, + ses-html ==0.4.0.0, + set-cover ==0.1.1, + setenv ==0.1.1.3, + setlocale ==1.0.0.10, + set-monad ==0.3.0.0, + sets ==0.0.6.2, + sexp-grammar ==2.3.4.2, + SHA ==1.6.4.4, + shake ==0.19.7, + shake-plus ==0.3.4.0, + shakespeare ==2.1.0.1, + shakespeare-text ==1.1.0, + shared-memory ==0.2.0.1, + ShellCheck ==0.9.0, + shell-conduit ==5.0.0, + shell-escape ==0.2.0, + shelltestrunner ==1.9.0.1, + shell-utility ==0.1, + shellwords ==0.1.3.1, + shelly ==1.12.1, + should-not-typecheck ==2.1.0, + show-combinators ==0.2.0.0, + shower ==0.2.0.3, + siggy-chardust ==1.0.0, + signal ==0.1.0.4, + silently ==1.2.5.3, + simple ==2.0.0, + simple-affine-space ==0.2.1, + simple-cabal ==0.1.3.1, + simple-cmd ==0.2.7, + simple-cmd-args ==0.1.8, + simple-expr ==0.1.1.0, + simple-media-timestamp ==0.2.1.0, + simple-media-timestamp-attoparsec ==0.1.0.0, + simple-prompt ==0.2.2, + simple-reflect ==0.3.3, + simple-sendfile ==0.2.32, + simple-session ==2.0.0, + simple-templates ==2.0.0, + simple-vec3 ==0.6.0.1, + since ==0.0.0, + singleton-bool ==0.1.6, + singleton-nats ==0.4.7, + singletons ==3.0.2, + singletons-base ==3.1.1, + singletons-presburger ==0.7.2.0, + singletons-th ==3.1.1, + Sit ==0.2022.3.18, + sitemap-gen ==0.1.0.0, + size-based ==0.1.3.2, + sized ==1.1.0.0, + skein ==1.0.9.4, + skews ==0.1.0.3, + skip-var ==0.1.1.0, + skylighting ==0.13.4.1, + skylighting-core ==0.13.4.1, + skylighting-format-ansi ==0.1, + skylighting-format-blaze-html ==0.1.1.1, + skylighting-format-context ==0.1.0.2, + skylighting-format-latex ==0.1, + slack-progressbar ==0.1.0.1, + slave-thread ==1.1.0.3, + slick ==1.2.1.0, + slist ==0.2.1.0, + slynx ==0.7.2.2, + smallcheck ==1.2.1.1, + smtp-mail ==0.3.0.0, + snap-blaze ==0.2.1.5, + snap-core ==1.0.5.1, + snowflake ==0.1.1.1, + socket ==0.8.3.0, + socks ==0.6.1, + solana-staking-csvs ==0.1.2.0, + some ==1.0.4.1, + some-dict-of ==0.1.0.2, + sop-core ==0.5.0.2, + sort ==1.0.0.0, + sorted-list ==0.2.1.2, + sound-collage ==0.2.1, + sourcemap ==0.1.7, + sox ==0.2.3.2, + soxlib ==0.0.3.2, + spacecookie ==1.0.0.2, + spatial-math ==0.2.7.0, + special-values ==0.1.0.0, + speculate ==0.4.14, + speedy-slice ==0.3.2, + splice ==0.6.1.1, + split ==0.2.3.5, + splitmix ==0.1.0.5, + splitmix-distributions ==1.0.0, + split-record ==0.1.1.4, + Spock ==0.14.0.0, + Spock-api ==0.14.0.0, + Spock-api-server ==0.14.0.0, + Spock-core ==0.14.0.1, + Spock-lucid ==0.4.0.1, + Spock-worker ==0.3.1.0, + spoon ==0.3.1, + spreadsheet ==0.1.3.10, + sqlcli ==0.2.2.0, + sqlcli-odbc ==0.2.0.1, + sqlite-simple ==0.4.18.2, + sql-words ==0.1.6.5, + squeather ==0.8.0.0, + srcloc ==0.6.0.1, + srt ==0.1.2.0, + srtree ==1.0.0.5, + stache ==2.3.4, + stack ==2.9.3.1, + stack-all ==0.4.2, + stack-clean-old ==0.4.8, + stack-templatizer ==0.1.1.0, + state-codes ==0.1.3, + stateref ==0.3, + statestack ==0.3.1.1, + StateVar ==1.2.2, + stateWriter ==0.4.0, + static-canvas ==0.2.0.3, + static-text ==0.2.0.7, + statistics ==0.16.2.1, + statistics-linreg ==0.3, + status-notifier-item ==0.3.1.0, + step-function ==0.2.0.1, + stitch ==0.6.0.0, + stm installed, + stm-chans ==3.0.0.9, + stm-conduit ==4.0.1, + stm-containers ==1.2.0.3, + stm-delay ==0.1.1.1, + stm-extras ==0.1.0.3, + stm-hamt ==1.2.0.14, + stm-lifted ==2.5.0.0, + STMonadTrans ==0.4.7, + stm-split ==0.0.2.1, + stopwatch ==0.1.0.6, + storable-complex ==0.2.3.0, + storable-endian ==0.2.6.1, + storable-record ==0.0.7, + storable-tuple ==0.1, + storablevector ==0.2.13.2, + store ==0.7.18, + store-core ==0.4.4.6, + store-streaming ==0.2.0.5, + stratosphere ==0.60.0, + Stream ==0.4.7.2, + streaming ==0.2.4.0, + streaming-attoparsec ==1.0.0.1, + streaming-bytestring ==0.3.2, + streaming-commons ==0.2.2.6, + streaming-wai ==0.1.1, + streamly ==0.9.0, + streamly-core ==0.1.0, + streamly-examples ==0.1.3, + streamly-process ==0.3.0, + streams ==3.3.2, + streamt ==0.5.0.1, + strict ==0.5, + strict-base-types ==0.8, + strict-concurrency ==0.2.4.3, + strict-lens ==0.4.0.3, + strict-list ==0.1.7.4, + strict-tuple ==0.1.5.3, + strict-wrapper ==0.0.0.0, + stringable ==0.1.3, + stringbuilder ==0.5.1, + string-combinators ==0.6.0.5, + string-conv ==0.2.0, + string-conversions ==0.4.0.1, + string-interpolate ==0.3.2.1, + stringprep ==1.0.0, + string-qq ==0.0.5, + string-random ==0.1.4.3, + stringsearch ==0.3.6.6, + string-transform ==1.1.1, + string-variants ==0.2.2.0, + stripe-concepts ==1.0.3.3, + stripe-scotty ==1.1.0.4, + stripe-signature ==1.0.0.16, + stripe-wreq ==1.0.1.16, + strive ==6.0.0.10, + structs ==0.1.9, + structured ==0.1.1, + structured-cli ==2.7.0.1, + subcategories ==0.2.0.1, + sundown ==0.6, + superbuffer ==0.3.1.2, + svg-builder ==0.1.1, + SVGFonts ==1.8.0.1, + svg-tree ==0.6.2.4, + swagger2 ==2.8.7, + swish ==0.10.7.0, + syb ==0.7.2.4, + sydtest ==0.15.1.1, + sydtest-aeson ==0.1.0.0, + sydtest-amqp ==0.1.0.0, + sydtest-autodocodec ==0.0.0.0, + sydtest-discover ==0.0.0.4, + sydtest-hedgehog ==0.4.0.0, + sydtest-hedis ==0.0.0.0, + sydtest-mongo ==0.0.0.0, + sydtest-persistent ==0.0.0.2, + sydtest-persistent-postgresql ==0.2.0.3, + sydtest-persistent-sqlite ==0.2.0.3, + sydtest-process ==0.0.0.0, + sydtest-rabbitmq ==0.1.0.0, + sydtest-servant ==0.2.0.2, + sydtest-typed-process ==0.0.0.0, + sydtest-wai ==0.2.0.1, + sydtest-webdriver ==0.0.0.1, + sydtest-webdriver-screenshot ==0.0.0.2, + sydtest-webdriver-yesod ==0.0.0.1, + sydtest-yesod ==0.3.0.2, + symbol ==0.2.4, + symengine ==0.1.2.0, + symmetry-operations-symbols ==0.0.2.1, + synthesizer-alsa ==0.5.0.6, + synthesizer-core ==0.8.3, + synthesizer-dimensional ==0.8.1.1, + synthesizer-midi ==0.6.1.2, + sysinfo ==0.1.1, + system-argv0 ==0.1.1, + systemd ==2.3.0, + systemd-socket-activation ==1.1.0.1, + system-fileio ==0.3.16.4, + system-filepath ==0.4.14, + system-info ==0.5.2, + tabular ==0.2.2.8, + tagchup ==0.4.1.2, + tagged ==0.8.7, + tagged-binary ==0.2.0.1, + tagged-identity ==0.1.4, + tagged-transformer ==0.8.2, + tagshare ==0.0, + tagsoup ==0.14.8, + tagstream-conduit ==0.5.6, + tao ==1.0.0, + tao-example ==1.0.0, + tar ==0.5.1.1, + tar-conduit ==0.3.2.1, + tardis ==0.4.4.0, + tasty ==1.4.3, + tasty-ant-xml ==1.1.9, + tasty-autocollect ==0.4.1, + tasty-bench ==0.3.5, + tasty-dejafu ==2.1.0.1, + tasty-discover ==5.0.0, + tasty-expected-failure ==0.12.3, + tasty-fail-fast ==0.0.3, + tasty-focus ==1.0.1, + tasty-golden ==2.3.5, + tasty-hedgehog ==1.4.0.1, + tasty-hslua ==1.1.0, + tasty-hspec ==1.2.0.3, + tasty-html ==0.4.2.1, + tasty-hunit ==0.10.1, + tasty-hunit-compat ==0.2.0.1, + tasty-inspection-testing ==0.2, + tasty-kat ==0.0.3, + tasty-leancheck ==0.0.2, + tasty-lua ==1.1.0, + tasty-program ==1.1.0, + tasty-quickcheck ==0.10.2, + tasty-rerun ==1.1.19, + tasty-silver ==3.3.1.3, + tasty-smallcheck ==0.8.2, + tasty-tap ==0.1.0, + tasty-th ==0.1.7, + tasty-wai ==0.1.2.0, + tce-conf ==1.3, + tcp-streams ==1.0.1.1, + tdigest ==0.3, + teardown ==0.5.0.1, + telegram-bot-api ==6.7.1, + telegram-bot-simple ==0.12, + template-haskell installed, + template-haskell-compat-v0208 ==0.1.9.3, + temporary ==1.3, + temporary-rc ==1.2.0.3, + temporary-resourcet ==0.1.0.1, + tensorflow-test ==0.1.0.0, + tensors ==0.1.5, + termbox ==1.1.0.2, + termbox-banana ==1.0.0, + termbox-bindings-c ==0.1.0.1, + termbox-bindings-hs ==0.1.1, + termbox-tea ==0.1.0.1, + terminal-progress-bar ==0.4.2, + terminal-size ==0.3.4, + terminfo installed, + termonad ==4.5.0.0, + test-framework ==0.8.2.0, + test-framework-hunit ==0.3.0.2, + test-framework-leancheck ==0.0.4, + test-framework-quickcheck2 ==0.3.0.5, + test-framework-smallcheck ==0.2, + test-fun ==0.1.0.0, + testing-feat ==1.1.1.1, + testing-type-modifiers ==0.1.0.1, + texmath ==0.12.8.4, + text installed, + text-ansi ==0.2.1.1, + text-binary ==0.2.1.1, + text-builder ==0.6.7, + text-builder-dev ==0.3.3.2, + text-builder-linear ==0.1.2, + text-conversions ==0.3.1.1, + text-format ==0.3.2.1, + text-icu ==0.8.0.4, + text-latin1 ==0.3.1, + text-ldap ==0.1.1.14, + textlocal ==0.1.0.5, + text-manipulate ==0.3.1.0, + text-metrics ==0.3.2, + text-postgresql ==0.0.3.1, + text-printer ==0.5.0.2, + text-regex-replace ==0.1.1.5, + text-rope ==0.2, + text-short ==0.1.5, + text-show ==3.10.4, + text-show-instances ==3.9.7, + text-zipper ==0.13, + tfp ==1.0.2, + tf-random ==0.5, + th-abstraction ==0.4.5.0, + th-bang-compat ==0.0.1.0, + th-compat ==0.1.4, + th-constraint-compat ==0.0.1.0, + th-data-compat ==0.1.3.0, + th-desugar ==1.14, + th-env ==0.1.1, + these ==1.2, + these-lens ==1.0.1.3, + these-optics ==1.0.1.2, + these-skinny ==0.7.5, + th-expand-syns ==0.4.11.0, + th-lego ==0.3.0.3, + th-lift ==0.8.4, + th-lift-instances ==0.1.20, + th-nowq ==0.1.0.5, + th-orphans ==0.13.14, + th-printf ==0.7, + thread-hierarchy ==0.3.0.2, + thread-local-storage ==0.2, + threads ==0.5.1.8, + threads-extras ==0.1.0.3, + thread-supervisor ==0.2.0.0, + th-reify-compat ==0.0.1.5, + th-reify-many ==0.1.10, + th-strict-compat ==0.1.0.1, + th-test-utils ==1.2.1, + th-utilities ==0.2.5.0, + thyme ==0.4, + tidal ==1.9.4, + tidal-link ==1.0.2, + tile ==0.3.0.0, + time installed, + time-compat ==1.9.6.1, + time-domain ==0.1.0.2, + timeit ==2.0, + time-lens ==0.4.0.2, + timelens ==0.2.0.2, + time-locale-compat ==0.1.1.5, + time-locale-vietnamese ==1.0.0.0, + time-manager ==0.0.1, + time-parsers ==0.2, + timerep ==2.1.0.0, + timers-tick ==0.5.0.4, + timer-wheel ==0.4.0.1, + timespan ==0.4.0.0, + time-units ==1.0.0, + time-units-types ==0.2.0.1, + timezone-olson ==0.2.1, + timezone-olson-th ==0.1.0.11, + timezone-series ==0.1.13, + titlecase ==1.0.1, + tls ==1.6.0, + tls-session-manager ==0.0.4, + tlynx ==0.7.2.2, + tmapchan ==0.0.3, + tmapmvar ==0.0.4, + tmp-postgres ==1.34.1.0, + tmp-proc ==0.5.1.4, + tmp-proc-postgres ==0.5.2.3, + tmp-proc-rabbitmq ==0.5.1.4, + tmp-proc-redis ==0.5.1.4, + token-bucket ==0.1.0.1, + toml-reader ==0.2.1.0, + toml-reader-parse ==0.1.1.1, + tophat ==1.0.7.0, + topograph ==1.0.0.2, + torrent ==10000.1.3, + torsor ==0.1, + tostring ==0.2.1.1, + tracing ==0.0.7.3, + tracing-control ==0.0.7.3, + transaction ==0.1.1.4, + transformers installed, + transformers-base ==0.4.6, + transformers-compat ==0.7.2, + transformers-either ==0.1.4, + transformers-fix ==1.0, + transient ==0.7.0.0, + traverse-with-class ==1.0.1.1, + tree-diff ==0.3.0.1, + tree-fun ==0.8.1.0, + tree-view ==0.5.1, + trie-simple ==0.4.2, + trifecta ==2.1.3, + trimdent ==0.1.0.0, + triplesec ==0.2.2.1, + trivial-constraint ==0.7.0.0, + tsv2csv ==0.1.0.2, + ttc ==1.2.1.0, + ttrie ==0.1.2.2, + tuple ==0.3.0.2, + tuples ==0.1.0.0, + tuples-homogenous-h98 ==0.1.1.0, + tuple-sop ==0.3.1.0, + tuple-th ==0.2.5, + turtle ==1.6.1, + twitter-conduit ==0.6.1, + twitter-types ==0.11.0, + twitter-types-lens ==0.11.0, + typecheck-plugin-nat-simple ==0.1.0.9, + typed-process ==0.2.11.1, + typed-uuid ==0.2.0.0, + type-equality ==1, + type-errors ==0.2.0.2, + type-fun ==0.1.3, + type-hint ==0.1, + type-level-integers ==0.0.1, + type-level-kv-list ==2.0.2.0, + type-level-natural-number ==2.0, + type-level-numbers ==0.1.1.2, + type-map ==0.1.7.0, + type-natural ==1.3.0.0, + typenums ==0.1.4, + type-of-html ==1.6.2.0, + type-of-html-static ==0.1.0.2, + type-rig ==0.1, + type-spec ==0.4.0.0, + typography-geometry ==1.0.1.0, + typst-symbols ==0.1.4, + tz ==0.1.3.6, + tzdata ==0.2.20230322.0, + tztime ==0.1.1.0, + ua-parser ==0.7.7.0, + uglymemo ==0.1.0.1, + ulid ==0.3.2.0, + unagi-chan ==0.4.1.4, + unbounded-delays ==0.1.1.1, + unbound-generics ==0.4.3, + unboxed-ref ==0.4.0.0, + unboxing-vector ==0.2.0.0, + uncaught-exception ==0.1.0, + unconstrained ==0.1.0.2, + unexceptionalio ==0.5.1, + unexceptionalio-trans ==0.5.1, + unfork ==1.0.0.1, + unicode ==0.0.1.1, + unicode-collation ==0.1.3.5, + unicode-data ==0.4.0.1, + unicode-show ==0.1.1.1, + unicode-transforms ==0.4.0.1, + unidecode ==0.1.0.4, + unification-fd ==0.11.2, + union ==0.1.2, + union-angle ==0.1.0.1, + unipatterns ==0.0.0.0, + uniplate ==1.6.13, + uniq-deep ==1.2.1, + unique ==0.0.1, + unique-logic ==0.4.0.1, + unique-logic-tf ==0.5.1, + unit-constraint ==0.0.0, + units-parser ==0.1.1.5, + universe ==1.2.2, + universe-base ==1.1.3.1, + universe-dependent-sum ==1.3, + universe-instances-extended ==1.1.3, + universe-reverse-instances ==1.1.1, + universe-some ==1.2.1, + universum ==1.8.2, + unix installed, + unix-bytestring ==0.4.0, + unix-compat ==0.7.1, + unix-time ==0.4.11, + unjson ==0.15.4, + unliftio ==0.2.25.0, + unliftio-core ==0.2.1.0, + unliftio-path ==0.0.2.0, + unliftio-pool ==0.4.2.0, + unlit ==0.4.0.0, + unordered-containers ==0.2.19.1, + unsafe ==0.0, + uri-bytestring ==0.3.3.1, + uri-bytestring-aeson ==0.1.0.8, + uri-encode ==1.5.0.7, + url ==2.1.3, + users ==0.5.0.0, + users-postgresql-simple ==0.5.0.2, + users-test ==0.5.0.1, + utf8-light ==0.4.4.0, + utf8-string ==1.0.2, + utility-ht ==0.0.17, + uuid ==1.3.15, + uuid-types ==1.0.5.1, + valida ==1.1.0, + valida-base ==0.2.0, + validate-input ==0.5.0.0, + validationt ==0.3.0, + validity ==0.12.0.2, + validity-aeson ==0.2.0.5, + validity-bytestring ==0.4.1.1, + validity-case-insensitive ==0.0.0.0, + validity-containers ==0.5.0.4, + validity-persistent ==0.0.0.0, + validity-primitive ==0.0.0.1, + validity-scientific ==0.2.0.3, + validity-text ==0.3.1.3, + validity-time ==0.5.0.0, + validity-unordered-containers ==0.2.0.3, + validity-uuid ==0.1.0.3, + validity-vector ==0.2.0.3, + valor ==1.0.0.0, + varying ==0.8.1.0, + vault ==0.3.1.5, + vcs-ignore ==0.0.2.0, + vec ==0.5, + vector ==0.13.1.0, + vector-algorithms ==0.9.0.1, + vector-binary-instances ==0.2.5.2, + vector-buffer ==0.4.1, + vector-builder ==0.3.8.5, + vector-bytes-instances ==0.1.1, + vector-extras ==0.2.8.1, + vector-hashtables ==0.1.1.4, + vector-instances ==3.4.2, + vector-mmap ==0.0.3, + vector-rotcev ==0.1.0.2, + vector-sized ==1.5.0, + vector-space ==0.16, + vector-split ==1.0.0.3, + vector-stream ==0.1.0.0, + vector-th-unbox ==0.2.2, + verbosity ==0.4.0.0, + versions ==6.0.3, + vformat ==0.14.1.0, + vformat-time ==0.1.0.0, + ViennaRNAParser ==1.3.3, + vinyl ==0.14.3, + vinyl-loeb ==0.0.1.0, + vivid ==0.5.2.0, + vivid-osc ==0.5.0.0, + vivid-supercollider ==0.4.1.2, + void ==0.7.3, + vty ==5.38, + wai ==3.2.4, + wai-app-static ==3.1.8, + wai-cli ==0.2.3, + wai-conduit ==3.0.0.4, + wai-control ==0.2.0.0, + wai-cors ==0.2.7, + wai-enforce-https ==1.0.0.0, + wai-eventsource ==3.0.0, + wai-extra ==3.1.13.0, + wai-feature-flags ==0.1.0.7, + wai-handler-launch ==3.0.3.1, + wai-logger ==2.4.0, + wai-middleware-bearer ==1.0.3, + wai-middleware-caching ==0.1.0.2, + wai-middleware-caching-lru ==0.1.0.0, + wai-middleware-caching-redis ==0.2.0.0, + wai-middleware-clacks ==0.1.0.1, + wai-middleware-delegate ==0.1.3.1, + wai-middleware-metrics ==0.2.4, + wai-middleware-prometheus ==1.0.0.1, + wai-middleware-static ==0.9.2, + wai-middleware-throttle ==0.3.0.1, + wai-rate-limit ==0.3.0.0, + wai-rate-limit-redis ==0.2.0.1, + wai-saml2 ==0.4, + wai-session ==0.3.3, + wai-session-postgresql ==0.2.1.3, + wai-session-redis ==0.1.0.5, + wai-slack-middleware ==0.2.0, + wai-websockets ==3.0.1.2, + wakame ==0.1.0.0, + warp ==3.3.25, + warp-tls ==3.3.6, + warp-tls-uid ==0.2.0.6, + wave ==0.2.1, + wcwidth ==0.0.2, + webdriver ==0.11.0.0, + webex-teams-api ==0.2.0.1, + webex-teams-conduit ==0.2.0.1, + webgear-core ==1.0.5, + webgear-openapi ==1.0.5, + webpage ==0.0.5.1, + web-routes ==0.27.15, + web-routes-boomerang ==0.28.4.4, + web-routes-happstack ==0.23.12.3, + web-routes-hsp ==0.24.6.2, + web-routes-th ==0.22.8.1, + web-routes-wai ==0.24.3.2, + webrtc-vad ==0.1.0.3, + websockets ==0.12.7.3, + weigh ==0.0.16, + welford-online-mean-variance ==0.2.0.0, + wide-word ==0.1.6.0, + Win32 installed, + Win32-notify ==0.3.0.3, + windns ==0.1.0.1, + witch ==1.2.0.3, + withdependencies ==0.3.0, + witherable ==0.4.2, + within ==0.2.0.1, + with-location ==0.1.0, + with-utf8 ==1.0.2.4, + witness ==0.6.2, + wizards ==1.0.3, + wl-pprint ==1.2.1, + wl-pprint-annotated ==0.1.0.1, + wl-pprint-text ==1.2.0.2, + word8 ==0.1.3, + word-compat ==0.0.6, + wordpress-auth ==1.0.0.1, + word-trie ==0.3.0, + word-wrap ==0.5, + world-peace ==1.0.2.0, + wrap ==0.0.0, + wreq ==0.5.4.2, + wreq-stringless ==0.5.9.1, + writer-cps-exceptions ==0.1.0.1, + writer-cps-mtl ==0.1.1.6, + writer-cps-transformers ==0.5.6.1, + wss-client ==0.3.0.0, + wuss ==2.0.1.3, + X11 ==1.10.3, + X11-xft ==0.3.4, + x11-xim ==0.0.9.0, + x509 ==1.7.7, + x509-store ==1.6.9, + x509-system ==1.6.7, + x509-validation ==1.6.12, + Xauth ==0.1, + xdg-basedir ==0.2.2, + xdg-desktop-entry ==0.1.1.1, + xdg-userdirs ==0.1.0.2, + xeno ==0.6, + xhtml installed, + xlsx ==1.1.1, + xml ==1.3.14, + xml-basic ==0.1.3.2, + xmlbf ==0.7, + xmlbf-xeno ==0.2.2, + xmlbf-xmlhtml ==0.2.2, + xml-conduit ==1.9.1.3, + xml-conduit-writer ==0.1.1.4, + xmlgen ==0.6.2.2, + xml-hamlet ==0.5.0.2, + xml-helpers ==1.0.0, + xmlhtml ==0.2.5.4, + xml-html-qq ==0.1.0.1, + xml-indexed-cursor ==0.1.1.0, + xml-lens ==0.3.1, + xml-parser ==0.1.1.1, + xml-picklers ==0.3.6, + xml-to-json-fast ==2.0.0, + xml-types ==0.3.8, + xmonad ==0.17.2, + xmonad-contrib ==0.17.1, + xor ==0.0.1.2, + xss-sanitize ==0.3.7.2, + xxhash-ffi ==0.2.0.0, + yaml ==0.11.11.2, + yaml-unscrambler ==0.1.0.18, + Yampa ==0.14.6, + yarn-lock ==0.6.5, + yeshql-core ==4.2.0.0, + yesod ==1.6.2.1, + yesod-auth ==1.6.11.2, + yesod-auth-basic ==0.1.0.3, + yesod-auth-hashdb ==1.7.1.7, + yesod-auth-oauth2 ==0.7.1.3, + yesod-auth-oidc ==0.1.4, + yesod-bin ==1.6.2.2, + yesod-core ==1.6.25.1, + yesod-eventsource ==1.6.0.1, + yesod-fb ==0.6.1, + yesod-form ==1.7.6, + yesod-form-bootstrap4 ==3.0.1.1, + yesod-gitrepo ==0.3.0, + yesod-gitrev ==0.2.2, + yesod-markdown ==0.12.6.13, + yesod-middleware-csp ==1.2.0, + yesod-newsfeed ==1.7.0.0, + yesod-page-cursor ==2.0.1.0, + yesod-paginator ==1.1.2.2, + yesod-persistent ==1.6.0.8, + yesod-recaptcha2 ==1.0.2.1, + yesod-routes-flow ==3.0.0.2, + yesod-sitemap ==1.6.0, + yesod-static ==1.6.1.0, + yesod-test ==1.6.16, + yesod-websockets ==0.3.0.3, + yes-precure5-command ==5.5.3, + yi-rope ==0.11, + yjsvg ==0.2.0.1, + yjtools ==0.9.18, + yoga ==0.0.0.5, + youtube ==0.2.1.1, + zenacy-html ==2.1.0, + zenacy-unicode ==1.0.2, + zeromq4-haskell ==0.8.0, + zeromq4-patterns ==0.3.1.0, + zigzag ==0.0.1.0, + zim-parser ==0.2.1.0, + zio ==0.1.0.2, + zip ==2.0.0, + zip-archive ==0.4.3, + zipper-extra ==0.1.3.2, + zippers ==0.3.2, + zip-stream ==0.2.2.0, + zlib ==0.6.3.0, + zlib-bindings ==0.1.1.5, + zot ==0.0.3, + zstd ==0.1.3.0 From 7fe8c13f542bc6f525abac5155bcc564aaa2a989 Mon Sep 17 00:00:00 2001 From: Phil de Joux Date: Sun, 10 Aug 2025 14:10:46 -0400 Subject: [PATCH 13/13] Remove repo --- .../ProjectImport/UniquePathDuplicates/cabal.out | 2 -- .../ProjectImport/UniquePathDuplicates/cabal.test.hs | 2 +- .../repo/hashable-1.4.2.0/hashable.cabal | 3 --- .../repo/hashable-1.4.3.0/hashable.cabal | 3 --- .../UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs | 4 ---- .../repo/some-exe-0.0.1.0/some-exe.cabal | 9 --------- 6 files changed, 1 insertion(+), 22 deletions(-) delete mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal delete mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal delete mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs delete mode 100644 cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out index 21160536202..61a197fdf7b 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.out @@ -1,5 +1,3 @@ -# cabal v2-update -Downloading the latest package list from test-local-repo # checking that we detect when the same config is imported via many different paths # cabal v2-build Warning: 2 imports of yops-4.config; diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs index 931705d36a7..a095682e3a1 100644 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/cabal.test.hs @@ -4,7 +4,7 @@ import Data.Function ((&)) import Data.Functor ((<&>)) import Data.List (isInfixOf) -main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do +main = cabalTest . recordMode RecordMarked $ do let log = recordHeader . pure -- The project is named yops as it is like hops but with y's for forks. diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal deleted file mode 100644 index de0cf79f7d8..00000000000 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.2.0/hashable.cabal +++ /dev/null @@ -1,3 +0,0 @@ -cabal-version: 1.12 -name: hashable -version: 1.4.2.0 diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal deleted file mode 100644 index b6475a1f15a..00000000000 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/hashable-1.4.3.0/hashable.cabal +++ /dev/null @@ -1,3 +0,0 @@ -cabal-version: 1.12 -name: hashable -version: 1.4.3.0 diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs deleted file mode 100644 index 33581fa8421..00000000000 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/Main.hs +++ /dev/null @@ -1,4 +0,0 @@ -module Main where - -main :: IO () -main = putStrLn "hello world" diff --git a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal b/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal deleted file mode 100644 index 3a2e620d96e..00000000000 --- a/cabal-testsuite/PackageTests/ProjectImport/UniquePathDuplicates/repo/some-exe-0.0.1.0/some-exe.cabal +++ /dev/null @@ -1,9 +0,0 @@ -name: some-exe -version: 0.0.1.0 -license: BSD3 -cabal-version: >= 1.2 -build-type: Simple - -Executable some-exe - main-is: Main.hs - build-depends: base