From dece5e847207052e3fecaab4e91aae1993cc2354 Mon Sep 17 00:00:00 2001 From: brandon s allbery kf8nh Date: Tue, 9 Apr 2024 17:53:00 -0400 Subject: [PATCH] Show provenance of import constraint With this change to the solver message rendering, I also fix some bugs around project imports, adding tests for those cases. Reviewers asked that the Y-shaped import checks (using IORef) be made on a separate pull request. Removing those lead to cascading deletions. - Regenerate expected .out files - Show tree provenance of import constraint - Add trimmed down PackageTests/VersionPriority - Add changelog entry - Use NonEmpty - Fix check for cyclical import - Use primes for next iteration - Remove unused LANGUAGE pragmas - Rename to projectConfigPathRoot - Docs for ProjectConfigPath and showProjectConfigPath - Renaming - Add cyclical import tests with 1 and 2 hops in cycle - Use full path for cyclical error message - Expected output has project with full project path - Add fullPath local function - Project directory as FilePath, not Maybe FilePath - Use (_, projectFileName) binding splitFileName - Need full path to project parsing legacy - Inline seenImports conversion - Add cyclical checks with same file names and hops - Add noncyclical tests that hop over folders - Add a project testing skipping in and out of a folder - Update expectations of cyclical tests - Use canonicalizePath for collapsing .. when possible - Capture trace for later - Add module for ProjectConfigPath - Move functions for ProjectConfigPath to its module - Fetch URI is not prefixed with ./https://etc - Document normaliseConfigPath - Add doctests for normaliseConfigPath - Add doctest of canonicalizeConfigPath - Show an example of canonical paths - Use importer and importee in canonicalizeConfigPaths - Add logging --- .../cabal-install-solver.cabal | 3 + .../Distribution/Solver/Modular/Message.hs | 3 + .../Solver/Types/ConstraintSource.hs | 7 +- .../Solver/Types/ProjectConfigPath.hs | 205 ++++++++++++++++++ .../src/Distribution/Client/ProjectConfig.hs | 12 +- .../Client/ProjectConfig/Legacy.hs | 129 +++++++---- .../Client/ProjectConfig/Types.hs | 12 +- .../Distribution/Client/ProjectPlanning.hs | 15 +- .../src/Distribution/Client/ScriptUtils.hs | 5 +- .../Distribution/Client/ProjectConfig.hs | 7 +- .../Distribution/Client/TreeDiffInstances.hs | 2 + .../ConditionalAndImport/cabal.out | 92 ++++++-- .../ConditionalAndImport/cabal.test.hs | 143 ++++++++++-- .../ConditionalAndImport/oops-0.project | 4 + .../ConditionalAndImport/oops-2.config | 1 + .../ConditionalAndImport/oops-4.config | 1 + .../ConditionalAndImport/oops-6.config | 1 + .../ConditionalAndImport/oops-8.config | 1 + .../ConditionalAndImport/oops/oops-1.config | 1 + .../ConditionalAndImport/oops/oops-3.config | 1 + .../ConditionalAndImport/oops/oops-5.config | 1 + .../ConditionalAndImport/oops/oops-7.config | 1 + .../ConditionalAndImport/oops/oops-9.config | 2 + .../ConditionalAndImport/oops/oops.cabal | 9 + .../repo/hashable-1.4.2.0/hashable.cabal | 3 + .../repo/hashable-1.4.3.0/hashable.cabal | 3 + .../noncyclical-same-filename-b.config | 2 +- .../PackageTests/VersionPriority/0-local.out | 6 +- .../PackageTests/VersionPriority/1-local.out | 14 +- .../PackageTests/VersionPriority/1-web.out | 14 +- .../PackageTests/VersionPriority/2-local.out | 16 +- .../PackageTests/VersionPriority/2-web.out | 16 +- .../PackageTests/VersionPriority/3-web.out | 18 +- .../repo/hashable-1.4.2.0/hashable.cabal | 183 ---------------- .../repo/hashable-1.4.3.0/hashable.cabal | 185 ---------------- changelog.d/issue-9578 | 26 +++ 36 files changed, 654 insertions(+), 490 deletions(-) create mode 100644 cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops-0.project create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops-2.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops-4.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops-6.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops-8.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-1.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-3.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-5.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-7.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-9.config create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops.cabal create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/repo/hashable-1.4.2.0/hashable.cabal create mode 100644 cabal-testsuite/PackageTests/ConditionalAndImport/repo/hashable-1.4.3.0/hashable.cabal create mode 100644 changelog.d/issue-9578 diff --git a/cabal-install-solver/cabal-install-solver.cabal b/cabal-install-solver/cabal-install-solver.cabal index 9977441d331..3f0e6b2bd20 100644 --- a/cabal-install-solver/cabal-install-solver.cabal +++ b/cabal-install-solver/cabal-install-solver.cabal @@ -92,6 +92,7 @@ library Distribution.Solver.Types.PackagePreferences Distribution.Solver.Types.PkgConfigDb Distribution.Solver.Types.Progress + Distribution.Solver.Types.ProjectConfigPath Distribution.Solver.Types.ResolverPackage Distribution.Solver.Types.Settings Distribution.Solver.Types.SolverId @@ -107,8 +108,10 @@ library , Cabal-syntax ^>=3.12 , containers >=0.5.6.2 && <0.8 , edit-distance ^>= 0.2.2 + , directory >= 1.3.7.0 && < 1.4 , filepath ^>=1.4.0.0 || ^>=1.5.0.0 , mtl >=2.0 && <2.4 + , network-uri >= 2.6.0.2 && < 2.7 , pretty ^>=1.1 , transformers >=0.4.2.0 && <0.7 , text (>= 1.2.3.0 && < 1.3) || (>= 2.0 && < 2.2) diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs index 11fa7ca874d..a8528efd102 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs @@ -31,8 +31,10 @@ import Distribution.Solver.Modular.Version import Distribution.Solver.Types.ConstraintSource import Distribution.Solver.Types.PackagePath import Distribution.Solver.Types.Progress +import Distribution.Solver.Types.ProjectConfigPath (docProjectConfigPathFailReason) import Distribution.Types.LibraryName import Distribution.Types.UnqualComponentName +import Text.PrettyPrint (nest, render) data Message = Enter -- ^ increase indentation level @@ -311,6 +313,7 @@ showFR _ NotExplicit = " (not a user-provided goal nor ment showFR _ Shadowed = " (shadowed by another installed package with same version)" showFR _ (Broken u) = " (package is broken, missing dependency " ++ prettyShow u ++ ")" showFR _ UnknownPackage = " (unknown package)" +showFR _ (GlobalConstraintVersion vr (ConstraintSourceProjectConfig pc)) = '\n' : (render . nest 6 $ docProjectConfigPathFailReason vr pc) showFR _ (GlobalConstraintVersion vr src) = " (" ++ constraintSource src ++ " requires " ++ prettyShow vr ++ ")" showFR _ (GlobalConstraintInstalled src) = " (" ++ constraintSource src ++ " requires installed instance)" showFR _ (GlobalConstraintSource src) = " (" ++ constraintSource src ++ " requires source instance)" diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs b/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs index dadf8bf08b1..3fdf64bde89 100644 --- a/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs +++ b/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs @@ -5,7 +5,8 @@ module Distribution.Solver.Types.ConstraintSource ) where import Distribution.Solver.Compat.Prelude -import Prelude () +import Distribution.Solver.Types.ProjectConfigPath (ProjectConfigPath, docProjectConfigPath) +import Text.PrettyPrint (render) -- | Source of a 'PackageConstraint'. data ConstraintSource = @@ -14,7 +15,7 @@ data ConstraintSource = ConstraintSourceMainConfig FilePath -- | Local cabal.project file - | ConstraintSourceProjectConfig FilePath + | ConstraintSourceProjectConfig ProjectConfigPath -- | User config file, which is ./cabal.config by default. | ConstraintSourceUserConfig FilePath @@ -60,7 +61,7 @@ showConstraintSource :: ConstraintSource -> String showConstraintSource (ConstraintSourceMainConfig path) = "main config " ++ path showConstraintSource (ConstraintSourceProjectConfig path) = - "project config " ++ path + "project config " ++ render (docProjectConfigPath path) showConstraintSource (ConstraintSourceUserConfig path)= "user config " ++ path showConstraintSource ConstraintSourceCommandlineFlag = "command line flag" showConstraintSource ConstraintSourceUserTarget = "user target" diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs new file mode 100644 index 00000000000..48141df39c3 --- /dev/null +++ b/cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs @@ -0,0 +1,205 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE LambdaCase #-} + +module Distribution.Solver.Types.ProjectConfigPath + ( + -- * Project Config Path Manipulation + ProjectConfigPath(..) + , projectConfigPathRoot + , nullProjectConfigPath + , consProjectConfigPath + + -- * Messages + , docProjectConfigPath + , cyclicalImportMsg + , docProjectConfigPathFailReason + + -- * Checks and Normalization + , isCyclicConfigPath + , canonicalizeConfigPath + ) where + +import Distribution.Solver.Compat.Prelude hiding (toList, (<>)) +import Prelude (sequence) + +import Data.Coerce (coerce) +import Data.List.NonEmpty ((<|)) +import Network.URI (parseURI) +import System.Directory +import System.FilePath +import qualified Data.List.NonEmpty as NE +import Distribution.Solver.Modular.Version (VR) +import Distribution.Pretty (prettyShow) +import Text.PrettyPrint + +-- | 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@. +-- +-- An import can be a URI, such as [a stackage +-- cabal.config](https://www.stackage.org/nightly/cabal.config), but we do not +-- support URIs in the middle of the path, URIs that import other URIs, or URIs +-- that import local files. +-- +-- List elements are relative to each other but once canonicalized, elements are +-- relative to the directory of the project root. +newtype ProjectConfigPath = ProjectConfigPath (NonEmpty FilePath) + deriving (Eq, Ord, Show, Generic) + +instance Binary ProjectConfigPath +instance Structured ProjectConfigPath + +-- | Renders the path like this; +-- @ +-- D.config +-- imported by: C.config +-- imported by: B.config +-- imported by: A.project +-- @ +-- >>> render . docProjectConfigPath $ ProjectConfigPath $ "D.config" :| ["C.config", "B.config", "A.project" ] +-- "D.config\n imported by: C.config\n imported by: B.config\n imported by: A.project" +docProjectConfigPath :: ProjectConfigPath -> Doc +docProjectConfigPath (ProjectConfigPath (p :| [])) = text p +docProjectConfigPath (ProjectConfigPath (p :| ps)) = vcat $ + text p : [ text " " <+> text "imported by:" <+> text l | l <- ps ] + +-- | A message for a cyclical import, assuming the head of the path is the +-- duplicate. +cyclicalImportMsg :: ProjectConfigPath -> Doc +cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) = + vcat + [ text "cyclical import of" <+> text duplicate <> semi + , nest 2 (docProjectConfigPath path) + ] + +docProjectConfigPathFailReason :: VR -> ProjectConfigPath -> Doc +docProjectConfigPathFailReason vr pcp + | ProjectConfigPath (p :| []) <- pcp = + constraint p + | ProjectConfigPath (p :| ps) <- pcp = vcat + [ constraint p + , cat [nest 2 $ text "imported by:" <+> text l | l <- ps ] + ] + where + pathRequiresVersion p = text p <+> text "requires" <+> text (prettyShow vr) + constraint p = parens $ text "constraint from" <+> pathRequiresVersion p + +-- | The root of the path, the project itself. +projectConfigPathRoot :: ProjectConfigPath -> FilePath +projectConfigPathRoot (ProjectConfigPath xs) = last xs + +-- | Used by some tests as a dummy "unused" project root. +nullProjectConfigPath :: ProjectConfigPath +nullProjectConfigPath = ProjectConfigPath $ "unused" :| [] + +-- | Check if the path has duplicates. A cycle of imports is not allowed. This +-- check should only be done after the path has been canonicalized with +-- @canonicalizeConfigPath@. This is because the import path may contain paths +-- that are the same in relation to their importers but different in relation to +-- the project root directory. +isCyclicConfigPath :: ProjectConfigPath -> Bool +isCyclicConfigPath (ProjectConfigPath p) = length p /= length (NE.nub p) + +-- | Prepends the path of the importee to the importer path. +consProjectConfigPath :: FilePath -> ProjectConfigPath -> ProjectConfigPath +consProjectConfigPath p ps = ProjectConfigPath (p <| coerce ps) + +-- | Make paths relative to the directory of the root of the project, not +-- relative to the file they were imported from. +makeRelativeConfigPath :: FilePath -> ProjectConfigPath -> ProjectConfigPath +makeRelativeConfigPath dir (ProjectConfigPath p) = + ProjectConfigPath + $ (\segment -> (if isURI segment then segment else makeRelative dir segment)) + <$> p + +-- | Normalizes and canonicalizes a path removing '.' and '..' indirections. +-- Makes the path relative to the given directory (typically the project root) +-- instead of relative to the file it was imported from. +-- +-- It converts paths like this: +-- @ +-- └─ hops-0.project +-- └─ hops/hops-1.config +-- └─ ../hops-2.config +-- └─ hops/hops-3.config +-- └─ ../hops-4.config +-- └─ hops/hops-5.config +-- └─ ../hops-6.config +-- └─ hops/hops-7.config +-- └─ ../hops-8.config +-- └─ hops/hops-9.config +-- @ +-- +-- Into paths like this: +-- @ +-- └─ hops-0.project +-- └─ hops/hops-1.config +-- └─ hops-2.config +-- └─ hops/hops-3.config +-- └─ hops-4.config +-- └─ hops/hops-5.config +-- └─ hops-6.config +-- └─ hops/hops-7.config +-- └─ hops-8.config +-- └─ hops/hops-9.config +-- @ +-- +-- That way we have @hops-8.config@ instead of +-- @./hops/../hops/../hops/../hops/../hops-8.config@. +-- +-- Let's see how @canonicalizePath@ works that is used in the implementation +-- then we'll see how @canonicalizeConfigPath@ works. +-- +-- >>> let d = testDir +-- >>> makeRelative d <$> canonicalizePath (d "hops/../hops/../hops/../hops/../hops-8.config") +-- "hops-8.config" +-- +-- >>> let d = testDir +-- >>> p <- canonicalizeConfigPath d (ProjectConfigPath $ (d "hops/../hops/../hops/../hops/../hops-8.config") :| []) +-- >>> render $ docProjectConfigPath p +-- "hops-8.config" +-- +-- >>> :{ +-- do +-- let expected = unlines +-- [ "hops/hops-9.config" +-- , " imported by: hops-8.config" +-- , " imported by: hops/hops-7.config" +-- , " imported by: hops-6.config" +-- , " imported by: hops/hops-5.config" +-- , " imported by: hops-4.config" +-- , " imported by: hops/hops-3.config" +-- , " imported by: hops-2.config" +-- , " imported by: hops/hops-1.config" +-- , " imported by: hops-0.project" +-- ] +-- let d = testDir +-- let configPath = ProjectConfigPath ("hops/hops-9.config" :| +-- [ "../hops-8.config" +-- , "hops/hops-7.config" +-- , "../hops-6.config" +-- , "hops/hops-5.config" +-- , "../hops-4.config" +-- , "hops/hops-3.config" +-- , "../hops-2.config" +-- , "hops/hops-1.config" +-- , d "hops-0.project"]) +-- p <- canonicalizeConfigPath d configPath +-- return $ expected == render (docProjectConfigPath p) ++ "\n" +-- :} +-- True +canonicalizeConfigPath :: FilePath -> ProjectConfigPath -> IO ProjectConfigPath +canonicalizeConfigPath d (ProjectConfigPath p) = do + xs <- sequence $ NE.scanr (\importee -> (>>= \importer -> + if isURI importee + then pure importee + else canonicalizePath $ d takeDirectory importer importee)) + (pure ".") p + return . makeRelativeConfigPath d . ProjectConfigPath . NE.fromList $ NE.init xs + +isURI :: FilePath -> Bool +isURI = isJust . parseURI + +-- $setup +-- >>> import Data.List +-- >>> testDir <- makeAbsolute =<< canonicalizePath "../cabal-testsuite/PackageTests/ConditionalAndImport" diff --git a/cabal-install/src/Distribution/Client/ProjectConfig.hs b/cabal-install/src/Distribution/Client/ProjectConfig.hs index 1a19eb3f621..a80f517765a 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig.hs @@ -8,6 +8,7 @@ module Distribution.Client.ProjectConfig ( -- * Types for project config ProjectConfig (..) + , ProjectConfigToParse (..) , ProjectConfigBuildOnly (..) , ProjectConfigShared (..) , ProjectConfigProvenance (..) @@ -57,6 +58,7 @@ module Distribution.Client.ProjectConfig ) where import Distribution.Client.Compat.Prelude +import Text.PrettyPrint (render) import Prelude () import Distribution.Client.Glob @@ -223,6 +225,8 @@ import System.IO , withBinaryFile ) +import Distribution.Solver.Types.ProjectConfigPath + ---------------------------------------- -- Resolving configuration to settings -- @@ -741,7 +745,7 @@ readProjectFileSkeleton then do monitorFiles [monitorFileHashed extensionFile] pcs <- liftIO readExtensionFile - monitorFiles $ map monitorFileHashed (projectSkeletonImports pcs) + monitorFiles $ map monitorFileHashed (projectConfigPathRoot <$> projectSkeletonImports pcs) pure pcs else do monitorFiles [monitorNonExistentFile extensionFile] @@ -751,7 +755,7 @@ readProjectFileSkeleton readExtensionFile = reportParseResult verbosity extensionDescription extensionFile - =<< parseProjectSkeleton distDownloadSrcDirectory httpTransport verbosity [] extensionFile + =<< parseProject extensionFile distDownloadSrcDirectory httpTransport verbosity . ProjectConfigToParse =<< BS.readFile extensionFile -- | Render the 'ProjectConfig' format. @@ -788,7 +792,7 @@ readGlobalConfig verbosity configFileFlag = do reportParseResult :: Verbosity -> String -> FilePath -> OldParser.ParseResult ProjectConfigSkeleton -> IO ProjectConfigSkeleton reportParseResult verbosity _filetype filename (OldParser.ParseOk warnings x) = do unless (null warnings) $ - let msg = unlines (map (OldParser.showPWarning (intercalate ", " $ filename : projectSkeletonImports x)) warnings) + let msg = unlines (map (OldParser.showPWarning (intercalate ", " $ filename : (projectConfigPathRoot <$> projectSkeletonImports x))) warnings) in warn verbosity msg return x reportParseResult verbosity filetype filename (OldParser.ParseFailed err) = @@ -872,7 +876,7 @@ renderBadPackageLocations (BadPackageLocations provenance bpls) renderExplicit = "When using configuration(s) from " - ++ intercalate ", " (mapMaybe getExplicit (Set.toList provenance)) + ++ intercalate ", " (render . docProjectConfigPath <$> mapMaybe getExplicit (Set.toList provenance)) ++ ", the following errors occurred:\n" ++ renderErrors renderBadPackageLocation diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs index d949437f5d6..3c9253c2b59 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs @@ -1,14 +1,15 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE ViewPatterns #-} -- | Project configuration, implementation in terms of legacy types. module Distribution.Client.ProjectConfig.Legacy ( -- Project config skeletons ProjectConfigSkeleton - , parseProjectSkeleton + , parseProject , instantiateProjectConfigSkeletonFetchingCompiler , instantiateProjectConfigSkeletonWithCompiler , singletonProjectConfigSkeleton @@ -30,6 +31,7 @@ module Distribution.Client.ProjectConfig.Legacy , renderPackageLocationToken ) where +import Data.Coerce (coerce) import Distribution.Client.Compat.Prelude import Distribution.Types.Flag (FlagName, parsecFlagAssignment) @@ -55,6 +57,7 @@ import Distribution.Client.CmdInstall.ClientInstallFlags import Distribution.Compat.Lens (toListOf, view) import Distribution.Solver.Types.ConstraintSource +import Distribution.Solver.Types.ProjectConfigPath import Distribution.Client.NixStyleOptions (NixStyleFlags (..)) import Distribution.Client.ProjectFlags (ProjectFlags (..), defaultProjectFlags, projectFlagsOptions) @@ -118,7 +121,8 @@ import Distribution.Simple.Setup , toFlag ) import Distribution.Simple.Utils - ( lowercase + ( debug + , lowercase ) import Distribution.Types.CondTree ( CondBranch (..) @@ -167,24 +171,24 @@ import Distribution.System (Arch, OS) import Distribution.Types.PackageVersionConstraint ( PackageVersionConstraint ) -import Text.PrettyPrint - ( Doc - , ($+$) - ) -import qualified Text.PrettyPrint as Disp import qualified Data.ByteString.Char8 as BS import qualified Data.Map as Map import qualified Data.Set as Set - import Network.URI (URI (..), parseURI) +import System.Directory (createDirectoryIfMissing, makeAbsolute) +import System.FilePath (isAbsolute, isPathSeparator, makeValid, splitFileName, ()) +import Text.PrettyPrint + ( Doc + , render + , ($+$) + ) +import qualified Text.PrettyPrint as Disp import Distribution.Fields.ConfVar (parseConditionConfVarFromClause) import Distribution.Client.HttpUtils import Distribution.Client.ReplFlags (multiReplOption) -import System.Directory (createDirectoryIfMissing) -import System.FilePath (isAbsolute, isPathSeparator, makeValid, takeDirectory, ()) ------------------------------------------------------------------ -- Handle extended project config files with conditionals and imports. @@ -192,9 +196,7 @@ import System.FilePath (isAbsolute, isPathSeparator, makeValid, takeDirectory, ( -- | ProjectConfigSkeleton is a tree of conditional blocks and imports wrapping a config. It can be finalized by providing the conditional resolution info -- and then resolving and downloading the imports -type ProjectConfigSkeleton = CondTree ConfVar [ProjectConfigImport] ProjectConfig - -type ProjectConfigImport = String +type ProjectConfigSkeleton = CondTree ConfVar [ProjectConfigPath] ProjectConfig singletonProjectConfigSkeleton :: ProjectConfig -> ProjectConfigSkeleton singletonProjectConfigSkeleton x = CondNode x mempty mempty @@ -212,7 +214,7 @@ instantiateProjectConfigSkeletonWithCompiler os arch impl _flags skel = go $ map go :: CondTree FlagName - [ProjectConfigImport] + [ProjectConfigPath] ProjectConfig -> ProjectConfig go (CondNode l _imps ts) = @@ -223,25 +225,60 @@ instantiateProjectConfigSkeletonWithCompiler os arch impl _flags skel = go $ map (Lit False) -> maybe ([]) ((: []) . go) mf _ -> error $ "unable to process condition: " ++ show cnd -- TODO it would be nice if there were a pretty printer -projectSkeletonImports :: ProjectConfigSkeleton -> [ProjectConfigImport] +projectSkeletonImports :: ProjectConfigSkeleton -> [ProjectConfigPath] projectSkeletonImports = view traverseCondTreeC -parseProjectSkeleton :: FilePath -> HttpTransport -> Verbosity -> [ProjectConfigImport] -> FilePath -> BS.ByteString -> IO (ParseResult ProjectConfigSkeleton) -parseProjectSkeleton cacheDir httpTransport verbosity seenImports source bs = (sanityWalkPCS False =<<) <$> liftPR (go []) (ParseUtils.readFields bs) +-- | Parses a project from its root config file, typically cabal.project. +parseProject + :: FilePath + -- ^ The root of the project configuration, typically cabal.project + -> FilePath + -> HttpTransport + -> Verbosity + -> ProjectConfigToParse + -- ^ The contents of the file to parse + -> IO (ParseResult 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 + +parseProjectSkeleton + :: FilePath + -> HttpTransport + -> Verbosity + -> FilePath + -- ^ The directory of the project configuration, typically the directory of cabal.project + -> ProjectConfigPath + -- ^ The path of the file being parsed, either the root or an import + -> ProjectConfigToParse + -- ^ The contents of the file to parse + -> IO (ParseResult ProjectConfigSkeleton) +parseProjectSkeleton cacheDir httpTransport verbosity projectDir source (ProjectConfigToParse bs) = + (sanityWalkPCS False =<<) <$> liftPR (go []) (ParseUtils.readFields bs) where go :: [ParseUtils.Field] -> [ParseUtils.Field] -> IO (ParseResult ProjectConfigSkeleton) go acc (x : xs) = case x of - (ParseUtils.F l "import" importLoc) -> - if importLoc `elem` seenImports - then pure . parseFail $ ParseUtils.FromString ("cyclical import of " ++ importLoc) (Just l) + (ParseUtils.F _ "import" importLoc) -> do + let importLocPath = importLoc `consProjectConfigPath` source + + -- Once we canonicalize the import path, we can check for cyclical imports + normLocPath <- canonicalizeConfigPath projectDir importLocPath + + debug verbosity $ "\nimport path, normalized\n=======================\n" ++ render (docProjectConfigPath normLocPath) + + if isCyclicConfigPath normLocPath + then pure . parseFail $ ParseUtils.FromString (render $ cyclicalImportMsg normLocPath) Nothing else do - let fs = fmap (\z -> CondNode z [importLoc] mempty) $ fieldsToConfig (reverse acc) - res <- parseProjectSkeleton cacheDir httpTransport verbosity (importLoc : seenImports) importLoc =<< fetchImportConfig importLoc + normSource <- canonicalizeConfigPath projectDir source + let fs = (\z -> CondNode z [normLocPath] mempty) <$> fieldsToConfig normSource (reverse acc) + res <- parseProjectSkeleton cacheDir httpTransport verbosity projectDir importLocPath . ProjectConfigToParse =<< fetchImportConfig normLocPath rest <- go [] xs pure . fmap mconcat . sequence $ [fs, res, rest] (ParseUtils.Section l "if" p xs') -> do subpcs <- go [] xs' - let fs = fmap singletonProjectConfigSkeleton $ fieldsToConfig (reverse acc) + let fs = singletonProjectConfigSkeleton <$> fieldsToConfig source (reverse acc) (elseClauses, rest) <- parseElseClauses xs let condNode = (\c pcs e -> CondNode mempty mempty [CondBranch c pcs e]) @@ -252,7 +289,9 @@ parseProjectSkeleton cacheDir httpTransport verbosity seenImports source bs = (s <*> elseClauses pure . fmap mconcat . sequence $ [fs, condNode, rest] _ -> go (x : acc) xs - go acc [] = pure . fmap singletonProjectConfigSkeleton . fieldsToConfig $ reverse acc + go acc [] = do + normSource <- canonicalizeConfigPath projectDir source + pure . fmap singletonProjectConfigSkeleton . fieldsToConfig normSource $ reverse acc parseElseClauses :: [ParseUtils.Field] -> IO (ParseResult (Maybe ProjectConfigSkeleton), ParseResult ProjectConfigSkeleton) parseElseClauses x = case x of @@ -271,8 +310,18 @@ parseProjectSkeleton cacheDir httpTransport verbosity seenImports source bs = (s pure (Just <$> condNode, rest) _ -> (\r -> (pure Nothing, r)) <$> go [] x - fieldsToConfig xs = fmap (addProvenance . convertLegacyProjectConfig) $ parseLegacyProjectConfigFields source xs - addProvenance x = x{projectConfigProvenance = Set.singleton (Explicit source)} + -- We want a normalized path for @fieldsToConfig@. This eventually surfaces + -- in solver rejection messages and build messages "this build was affected + -- by the following (project) config files" so we want all paths shown there + -- to be relative to the directory of the project, not relative to the file + -- they were imported from. + fieldsToConfig :: ProjectConfigPath -> [ParseUtils.Field] -> ParseResult ProjectConfig + fieldsToConfig sourceConfigPath xs = + addProvenance sourceConfigPath . convertLegacyProjectConfig + <$> parseLegacyProjectConfigFields sourceConfigPath xs + + addProvenance :: ProjectConfigPath -> ProjectConfig -> ProjectConfig + addProvenance sourcePath x = x{projectConfigProvenance = Set.singleton $ Explicit sourcePath} adaptParseError _ (Right x) = pure x adaptParseError l (Left e) = parseFail $ ParseUtils.FromString (show e) (Just l) @@ -284,8 +333,13 @@ parseProjectSkeleton cacheDir httpTransport verbosity seenImports source bs = (s addWarnings x' = x' liftPR _ (ParseFailed e) = pure $ ParseFailed e - fetchImportConfig :: ProjectConfigImport -> IO BS.ByteString - fetchImportConfig pci = case parseURI pci of + fetchImportConfig :: ProjectConfigPath -> IO BS.ByteString + fetchImportConfig (ProjectConfigPath (pci :| _)) = do + debug verbosity $ "fetching import: " ++ pci + fetch pci + + fetch :: FilePath -> IO BS.ByteString + fetch pci = case parseURI pci of Just uri -> do let fp = cacheDir map (\x -> if isPathSeparator x then '_' else x) (makeValid $ show uri) createDirectoryIfMissing True cacheDir @@ -293,7 +347,7 @@ parseProjectSkeleton cacheDir httpTransport verbosity seenImports source bs = (s BS.readFile fp Nothing -> BS.readFile $ - if isAbsolute pci then pci else takeDirectory source pci + if isAbsolute pci then pci else coerce projectDir pci modifiesCompiler :: ProjectConfig -> Bool modifiesCompiler pc = isSet projectConfigHcFlavor || isSet projectConfigHcPath || isSet projectConfigHcPkg @@ -305,8 +359,8 @@ parseProjectSkeleton cacheDir httpTransport verbosity seenImports source bs = (s | underConditional && modifiesCompiler d = parseFail $ ParseUtils.FromString "Cannot set compiler in a conditional clause of a cabal project file" Nothing | otherwise = mapM_ sanityWalkBranch comps >> pure t - sanityWalkBranch :: CondBranch ConfVar [ProjectConfigImport] ProjectConfig -> ParseResult () - sanityWalkBranch (CondBranch _c t f) = traverse (sanityWalkPCS True) f >> sanityWalkPCS True t >> pure () + sanityWalkBranch :: CondBranch ConfVar [ProjectConfigPath] ProjectConfig -> ParseResult () + sanityWalkBranch (CondBranch _c t f) = traverse_ (sanityWalkPCS True) f >> sanityWalkPCS True t >> pure () ------------------------------------------------------------------ -- Representing the project config file in terms of legacy types @@ -1177,18 +1231,17 @@ convertToLegacyPerPackageConfig PackageConfig{..} = -- Parsing and showing the project config file -- -parseLegacyProjectConfigFields :: FilePath -> [ParseUtils.Field] -> ParseResult LegacyProjectConfig -parseLegacyProjectConfigFields source = +parseLegacyProjectConfigFields :: ProjectConfigPath -> [ParseUtils.Field] -> ParseResult LegacyProjectConfig +parseLegacyProjectConfigFields (ConstraintSourceProjectConfig -> constraintSrc) = parseFieldsAndSections (legacyProjectConfigFieldDescrs constraintSrc) legacyPackageConfigSectionDescrs legacyPackageConfigFGSectionDescrs mempty - where - constraintSrc = ConstraintSourceProjectConfig source parseLegacyProjectConfig :: FilePath -> BS.ByteString -> ParseResult LegacyProjectConfig -parseLegacyProjectConfig source bs = parseLegacyProjectConfigFields source =<< ParseUtils.readFields bs +parseLegacyProjectConfig rootConfig bs = + parseLegacyProjectConfigFields (ProjectConfigPath $ rootConfig :| []) =<< ParseUtils.readFields bs showLegacyProjectConfig :: LegacyProjectConfig -> String showLegacyProjectConfig config = @@ -1203,7 +1256,7 @@ showLegacyProjectConfig config = -- Note: ConstraintSource is unused when pretty-printing. We fake -- it here to avoid having to pass it on call-sites. It's not great -- but requires re-work of how we annotate provenance. - constraintSrc = ConstraintSourceProjectConfig "unused" + constraintSrc = ConstraintSourceProjectConfig nullProjectConfigPath legacyProjectConfigFieldDescrs :: ConstraintSource -> [FieldDescr LegacyProjectConfig] legacyProjectConfigFieldDescrs constraintSrc = diff --git a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs index 744a50ddc37..3e8e3ba1b07 100644 --- a/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs +++ b/cabal-install/src/Distribution/Client/ProjectConfig/Types.hs @@ -6,6 +6,7 @@ module Distribution.Client.ProjectConfig.Types ( -- * Types for project config ProjectConfig (..) + , ProjectConfigToParse (..) , ProjectConfigBuildOnly (..) , ProjectConfigShared (..) , ProjectConfigProvenance (..) @@ -26,6 +27,7 @@ module Distribution.Client.ProjectConfig.Types import Distribution.Client.Compat.Prelude import Prelude () +import qualified Data.ByteString.Char8 as BS import Distribution.Client.BuildReports.Types ( ReportLevel (..) ) @@ -94,12 +96,18 @@ import Distribution.Version ) import qualified Data.Map as Map +import Distribution.Solver.Types.ProjectConfigPath (ProjectConfigPath) import Distribution.Types.ParStrat ------------------------------- -- Project config types -- +-- | The project configuration is configuration that is parsed but parse +-- configuration may import more configuration. Holds the unparsed contents of +-- an imported file contributing to the project config. +newtype ProjectConfigToParse = ProjectConfigToParse BS.ByteString + -- | This type corresponds directly to what can be written in the -- @cabal.project@ file. Other sources of configuration can also be injected -- into this type, such as the user-wide config file and the @@ -238,8 +246,8 @@ data ProjectConfigProvenance -- for how implicit configuration is determined. Implicit | -- | The path the project configuration was explicitly read from. - -- | The configuration was explicitly read from the specified 'FilePath'. - Explicit FilePath + -- | The configuration was explicitly read from the specified 'ProjectConfigPath'. + Explicit ProjectConfigPath deriving (Eq, Ord, Show, Generic) -- | Project configuration that is specific to each package, that is where we diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning.hs b/cabal-install/src/Distribution/Client/ProjectPlanning.hs index 6344249a8a6..cdda93c50b3 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanning.hs @@ -98,6 +98,7 @@ module Distribution.Client.ProjectPlanning ) where import Distribution.Client.Compat.Prelude +import Text.PrettyPrint (render) import Prelude () import Distribution.Client.Config @@ -208,6 +209,7 @@ import qualified Data.List.NonEmpty as NE import qualified Data.Map as Map import qualified Data.Set as Set import Distribution.Client.Errors +import Distribution.Solver.Types.ProjectConfigPath import System.FilePath import Text.PrettyPrint (colon, comma, fsep, hang, punctuate, quotes, text, vcat, ($$)) import qualified Text.PrettyPrint as Disp @@ -384,12 +386,13 @@ rebuildProjectConfig localPackages <- phaseReadLocalPackages (projectConfig <> cliConfig) return (projectConfig, localPackages) - info verbosity $ - unlines $ - ("this build was affected by the following (project) config files:" :) $ - [ "- " ++ path - | Explicit path <- Set.toList $ projectConfigProvenance projectConfig - ] + sequence_ + [ do + info verbosity . render . vcat $ + text "this build was affected by the following (project) config files:" + : [text "-" <+> docProjectConfigPath path] + | Explicit path <- Set.toList $ projectConfigProvenance projectConfig + ] return (projectConfig <> cliConfig, localPackages) where diff --git a/cabal-install/src/Distribution/Client/ScriptUtils.hs b/cabal-install/src/Distribution/Client/ScriptUtils.hs index 1793f6aa07d..676486d343d 100644 --- a/cabal-install/src/Distribution/Client/ScriptUtils.hs +++ b/cabal-install/src/Distribution/Client/ScriptUtils.hs @@ -59,8 +59,9 @@ import Distribution.Client.ProjectConfig import Distribution.Client.ProjectConfig.Legacy ( ProjectConfigSkeleton , instantiateProjectConfigSkeletonFetchingCompiler - , parseProjectSkeleton + , parseProject ) +import Distribution.Client.ProjectConfig.Types (ProjectConfigToParse (..)) import Distribution.Client.ProjectFlags ( flagIgnoreProject ) @@ -510,7 +511,7 @@ readProjectBlockFromScript verbosity httpTransport DistDirLayout{distDownloadSrc Left _ -> return mempty Right x -> reportParseResult verbosity "script" scriptName - =<< parseProjectSkeleton distDownloadSrcDirectory httpTransport verbosity [] scriptName x + =<< parseProject scriptName distDownloadSrcDirectory httpTransport verbosity (ProjectConfigToParse x) -- | Extract the first encountered script metadata block started end -- terminated by the tokens diff --git a/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs b/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs index cdb34a3534c..abdc1e79390 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/ProjectConfig.hs @@ -18,6 +18,7 @@ import Control.Monad import Data.Either (isRight) import Data.Foldable (for_) import Data.List (intercalate, isPrefixOf, (\\)) +import Data.List.NonEmpty (NonEmpty (..)) import Data.Map (Map) import qualified Data.Map as Map import Data.Maybe (fromMaybe) @@ -53,6 +54,7 @@ import Distribution.Verbosity (silent) import Distribution.Solver.Types.ConstraintSource import Distribution.Solver.Types.PackageConstraint +import Distribution.Solver.Types.ProjectConfigPath import Distribution.Solver.Types.Settings import Distribution.Client.ProjectConfig @@ -645,11 +647,10 @@ instance Arbitrary ProjectConfigShared where postShrink_Constraints = map (\uc -> (uc, projectConfigConstraintSource)) projectConfigConstraintSource :: ConstraintSource -projectConfigConstraintSource = - ConstraintSourceProjectConfig "unused" +projectConfigConstraintSource = ConstraintSourceProjectConfig nullProjectConfigPath instance Arbitrary ProjectConfigProvenance where - arbitrary = elements [Implicit, Explicit "cabal.project"] + arbitrary = elements [Implicit, Explicit (ProjectConfigPath $ "cabal.project" :| [])] instance Arbitrary PackageConfig where arbitrary = diff --git a/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs b/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs index 495c4cbf402..0dede72858a 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/TreeDiffInstances.hs @@ -6,6 +6,7 @@ module UnitTests.Distribution.Client.TreeDiffInstances () where import Distribution.Solver.Types.ConstraintSource import Distribution.Solver.Types.OptionalStanza import Distribution.Solver.Types.PackageConstraint +import Distribution.Solver.Types.ProjectConfigPath import Distribution.Solver.Types.Settings import Distribution.Client.BuildReports.Types @@ -39,6 +40,7 @@ instance ToExpr AllowOlder instance ToExpr BuildReport instance ToExpr ClientInstallFlags instance ToExpr CombineStrategy +instance ToExpr ProjectConfigPath instance ToExpr ConstraintSource instance ToExpr CountConflicts instance ToExpr FineGrainedConflicts diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out index fa224a62cae..e14881e8581 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out @@ -13,33 +13,53 @@ Warning: The directory /cabal.dist/home/.cabal/store/ghc-/incoming # checking cyclical loopback of a project importing itself # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-0-self.project:3: -cyclical import of cyclical-0-self.project +Error parsing project file /cyclical-0-self.project: +cyclical import of cyclical-0-self.project; + cyclical-0-self.project + imported by: cyclical-0-self.project # checking cyclical with hops; out and back # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-1-out-back.project:3: -cyclical import of cyclical-1-out-back.config +Error parsing project file /cyclical-1-out-back.project: +cyclical import of cyclical-1-out-back.project; + cyclical-1-out-back.project + imported by: cyclical-1-out-back.config + imported by: cyclical-1-out-back.project # checking cyclical with hops; out to a config that imports itself # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-1-out-self.project:1: -cyclical import of cyclical-1-out-self.config +Error parsing project file /cyclical-1-out-self.project: +cyclical import of cyclical-1-out-self.config; + cyclical-1-out-self.config + imported by: cyclical-1-out-self.config + imported by: cyclical-1-out-self.project # checking cyclical with hops; out, out, twice back # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-2-out-out-backback.project:3: -cyclical import of cyclical-2-out-out-backback-a.config +Error parsing project file /cyclical-2-out-out-backback.project: +cyclical import of cyclical-2-out-out-backback.project; + cyclical-2-out-out-backback.project + imported by: cyclical-2-out-out-backback-b.config + imported by: cyclical-2-out-out-backback-a.config + imported by: cyclical-2-out-out-backback.project # checking cyclical with hops; out, out, once back # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-2-out-out-back.project:1: -cyclical import of cyclical-2-out-out-back-a.config +Error parsing project file /cyclical-2-out-out-back.project: +cyclical import of cyclical-2-out-out-back-a.config; + cyclical-2-out-out-back-a.config + imported by: cyclical-2-out-out-back-b.config + imported by: cyclical-2-out-out-back-a.config + imported by: cyclical-2-out-out-back.project # checking cyclical with hops; out, out to a config that imports itself # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-2-out-out-self.project:1: -cyclical import of cyclical-2-out-out-self-b.config +Error parsing project file /cyclical-2-out-out-self.project: +cyclical import of cyclical-2-out-out-self-b.config; + cyclical-2-out-out-self-b.config + imported by: cyclical-2-out-out-self-b.config + imported by: cyclical-2-out-out-self-a.config + imported by: cyclical-2-out-out-self.project # checking that cyclical check doesn't false-positive on same file names in different folders; hoping within a folder and then into a subfolder # cabal v2-build Resolving dependencies... @@ -51,23 +71,59 @@ Preprocessing library for my-0.1... Building library for my-0.1... # checking that cyclical check doesn't false-positive on same file names in different folders; hoping into a subfolder and then back out again # cabal v2-build +Up to date # checking that cyclical check catches a same file name that imports itself # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-same-filename-out-out-self.project:1: -cyclical import of cyclical-same-filename-out-out-self.config +Error parsing project file /cyclical-same-filename-out-out-self.project: +cyclical import of same-filename/cyclical-same-filename-out-out-self.config; + same-filename/cyclical-same-filename-out-out-self.config + imported by: same-filename/cyclical-same-filename-out-out-self.config + imported by: cyclical-same-filename-out-out-self.config + imported by: cyclical-same-filename-out-out-self.project # checking that cyclical check catches importing its importer (with the same file name) # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-same-filename-out-out-backback.project:3: -cyclical import of cyclical-same-filename-out-out-backback.config +Error parsing project file /cyclical-same-filename-out-out-backback.project: +cyclical import of cyclical-same-filename-out-out-backback.project; + cyclical-same-filename-out-out-backback.project + imported by: same-filename/cyclical-same-filename-out-out-backback.config + imported by: cyclical-same-filename-out-out-backback.config + imported by: cyclical-same-filename-out-out-backback.project # checking that cyclical check catches importing its importer's importer (hopping over same file names) # cabal v2-build Error: [Cabal-7090] -Error parsing project file /cyclical-same-filename-out-out-back.project:1: -cyclical import of same-filename/cyclical-same-filename-out-out-back.config +Error parsing project file /cyclical-same-filename-out-out-back.project: +cyclical import of cyclical-same-filename-out-out-back.config; + cyclical-same-filename-out-out-back.config + imported by: same-filename/cyclical-same-filename-out-out-back.config + imported by: cyclical-same-filename-out-out-back.config + imported by: cyclical-same-filename-out-out-back.project # checking that imports work skipping into a subfolder and then back out again and again # cabal v2-build +Up to date +# checking conflicting constraints skipping into a subfolder and then back out again and again +# cabal v2-build +Resolving dependencies... +Error: [Cabal-7107] +Could not resolve dependencies: +[__0] trying: oops-0.1 (user goal) +[__1] next goal: hashable (dependency of oops) +[__1] rejecting: hashable-1.4.3.0 + (constraint from oops/oops-9.config requires ==1.4.2.0) + imported by: oops-8.config + imported by: oops/oops-7.config + imported by: oops-6.config + imported by: oops/oops-5.config + imported by: oops-4.config + imported by: oops/oops-3.config + imported by: oops-2.config + imported by: oops/oops-1.config + imported by: oops-0.project +[__1] rejecting: hashable-1.4.2.0 + (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 bad conditional # cabal v2-build Error: [Cabal-7090] diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs index 7998ee8075d..651658c441a 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/cabal.test.hs @@ -18,8 +18,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- etc log "checking cyclical with hops; out and back" cyclical1a <- fails $ cabal' "v2-build" [ "--project-file=cyclical-1-out-back.project" ] - -- This test should pass the following check but doesn't: - -- assertOutputContains "cyclical import of cyclical-1-out-back.project" cyclical1a + assertOutputContains "cyclical import of cyclical-1-out-back.project" cyclical1a -- +-- cyclical-1-out-self.project -- +-- cyclical-1-out-self.config (imports cyclical-1-out-self.config) @@ -36,8 +35,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- etc log "checking cyclical with hops; out, out, twice back" cyclical2a <- fails $ cabal' "v2-build" [ "--project-file=cyclical-2-out-out-backback.project" ] - -- This test should pass the following check but doesn't: - -- assertOutputContains "cyclical import of cyclical-2-out-out-backback.project" cyclical2a + assertOutputContains "cyclical import of cyclical-2-out-out-backback.project" cyclical2a -- +-- cyclical-2-out-out-back.project -- +-- cyclical-2-out-out-back-a.config @@ -68,7 +66,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- same-filename/noncyclical-same-filename-b.config -- +-- noncyclical-same-filename-b.config (no further imports so not cyclical) log "checking that cyclical check doesn't false-positive on same file names in different folders; hoping into a subfolder and then back out again" - cyclical3c <- fails $ cabal' "v2-build" [ "--project-file=noncyclical-same-filename-b.project" ] + cyclical3c <- cabal' "v2-build" [ "--project-file=noncyclical-same-filename-b.project" ] assertOutputDoesNotContain "cyclical import of" cyclical3c -- +-- cyclical-same-filename-out-out-self.project @@ -78,7 +76,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- etc log "checking that cyclical check catches a same file name that imports itself" cyclical4a <- fails $ cabal' "v2-build" [ "--project-file=cyclical-same-filename-out-out-self.project" ] - assertOutputContains "cyclical import of cyclical-same-filename-out-out-self.config" cyclical4a + assertOutputContains "cyclical import of same-filename/cyclical-same-filename-out-out-self.config" cyclical4a -- +-- cyclical-same-filename-out-out-backback.project -- +-- cyclical-same-filename-out-out-backback.config @@ -87,8 +85,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- etc log "checking that cyclical check catches importing its importer (with the same file name)" cyclical4b <- fails $ cabal' "v2-build" [ "--project-file=cyclical-same-filename-out-out-backback.project" ] - -- This test should pass the following check but doesn't: - -- assertOutputContains "cyclical import of cyclical-same-filename-out-out-backback.project" cyclical4b + assertOutputContains "cyclical import of cyclical-same-filename-out-out-backback.project" cyclical4b -- +-- cyclical-same-filename-out-out-back.project -- +-- cyclical-same-filename-out-out-back.config @@ -97,8 +94,7 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- etc log "checking that cyclical check catches importing its importer's importer (hopping over same file names)" cyclical4c <- fails $ cabal' "v2-build" [ "--project-file=cyclical-same-filename-out-out-back.project" ] - -- This test should pass the following check but doesn't: - -- assertOutputContains "cyclical import of cyclical-same-filename-out-out-back.config" cyclical4c + assertOutputContains "cyclical import of cyclical-same-filename-out-out-back.config" cyclical4c -- +-- hops-0.project -- +-- hops/hops-1.config @@ -111,19 +107,120 @@ main = cabalTest . withRepo "repo" . recordMode RecordMarked $ do -- +-- hops-8.config -- +-- hops/hops-9.config (no further imports so not cyclical) log "checking that imports work skipping into a subfolder and then back out again and again" - -- This test should pass the following checks but doesn't, it fails (but it shouldn't): - hopping <- fails $ cabal' "v2-build" [ "--project-file=hops-0.project" ] - -- assertOutputContains "this build was affected by the following (project) config files:" hopping - -- assertOutputContains "hops-0.project" hopping - -- assertOutputContains "../hops-2.config" hopping - -- assertOutputContains "../hops-4.config" hopping - -- assertOutputContains "../hops-6.config" hopping - -- assertOutputContains "../hops-8.config" hopping - -- assertOutputContains "hops/hops-1.config" hopping - -- assertOutputContains "hops/hops-3.config" hopping - -- assertOutputContains "hops/hops-5.config" hopping - -- assertOutputContains "hops/hops-7.config" hopping - -- assertOutputContains "hops/hops-9.config" hopping + hopping <- cabal' "v2-build" [ "--project-file=hops-0.project" ] + assertOutputContains "this build was affected by the following (project) config files:" hopping + assertOutputContains "- hops-0.project" hopping + + assertOutputContains + "- hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops-4.config \ + \ imported by: hops/hops-3.config \ + \ imported by: hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops-6.config \ + \ imported by: hops/hops-5.config \ + \ imported by: hops-4.config \ + \ imported by: hops/hops-3.config \ + \ imported by: hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops-8.config \ + \ imported by: hops/hops-7.config \ + \ imported by: hops-6.config \ + \ imported by: hops/hops-5.config \ + \ imported by: hops-4.config \ + \ imported by: hops/hops-3.config \ + \ imported by: hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops/hops-3.config \ + \ imported by: hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops/hops-5.config \ + \ imported by: hops-4.config \ + \ imported by: hops/hops-3.config \ + \ imported by: hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops/hops-7.config \ + \ imported by: hops-6.config \ + \ imported by: hops/hops-5.config \ + \ imported by: hops-4.config \ + \ imported by: hops/hops-3.config \ + \ imported by: hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + assertOutputContains + "- hops/hops-9.config \ + \ imported by: hops-8.config \ + \ imported by: hops/hops-7.config \ + \ imported by: hops-6.config \ + \ imported by: hops/hops-5.config \ + \ imported by: hops-4.config \ + \ imported by: hops/hops-3.config \ + \ imported by: hops-2.config \ + \ imported by: hops/hops-1.config \ + \ imported by: hops-0.project" + hopping + + -- The project is named oops as it is like hops but has conflicting constraints. + -- +-- oops-0.project + -- +-- oops/oops-1.config + -- +-- oops-2.config + -- +-- oops/oops-3.config + -- +-- oops-4.config + -- +-- oops/oops-5.config + -- +-- oops-6.config + -- +-- oops/oops-7.config + -- +-- oops-8.config + -- +-- oops/oops-9.config (has conflicting constraints) + log "checking conflicting constraints skipping into a subfolder and then back out again and again" + oopsing <- fails $ cabal' "v2-build" [ "all", "--project-file=oops-0.project" ] + assertOutputContains "rejecting: hashable-1.4.2.0" oopsing + assertOutputContains "rejecting: hashable-1.4.3.0" oopsing + assertOutputContains "(constraint from oops-0.project requires ==1.4.3.0)" oopsing + + assertOutputContains + " (constraint from oops/oops-9.config requires ==1.4.2.0) \ + \ imported by: oops-8.config \ + \ imported by: oops/oops-7.config \ + \ imported by: oops-6.config \ + \ imported by: oops/oops-5.config \ + \ imported by: oops-4.config \ + \ imported by: oops/oops-3.config \ + \ imported by: oops-2.config \ + \ imported by: oops/oops-1.config \ + \ imported by: oops-0.project" + oopsing log "checking bad conditional" badIf <- fails $ cabal' "v2-build" [ "--project-file=bad-conditional.project" ] diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops-0.project b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-0.project new file mode 100644 index 00000000000..c66f042c7f6 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-0.project @@ -0,0 +1,4 @@ +packages: ./oops/oops.cabal + +import: oops/oops-1.config +constraints: hashable ==1.4.3.0 diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops-2.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-2.config new file mode 100644 index 00000000000..a8fc298eb26 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-2.config @@ -0,0 +1 @@ +import: oops/oops-3.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops-4.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-4.config new file mode 100644 index 00000000000..904b9f8d1e4 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-4.config @@ -0,0 +1 @@ +import: oops/oops-5.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops-6.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-6.config new file mode 100644 index 00000000000..78251069a25 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-6.config @@ -0,0 +1 @@ +import: oops/oops-7.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops-8.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-8.config new file mode 100644 index 00000000000..34156d78b37 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops-8.config @@ -0,0 +1 @@ +import: oops/oops-9.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-1.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-1.config new file mode 100644 index 00000000000..27afba05e1f --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-1.config @@ -0,0 +1 @@ +import: ../oops-2.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-3.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-3.config new file mode 100644 index 00000000000..d71ae82df04 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-3.config @@ -0,0 +1 @@ +import: ../oops-4.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-5.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-5.config new file mode 100644 index 00000000000..8f572fe21ee --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-5.config @@ -0,0 +1 @@ +import: ../oops-6.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-7.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-7.config new file mode 100644 index 00000000000..34b2fea1201 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-7.config @@ -0,0 +1 @@ +import: ../oops-8.config diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-9.config b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-9.config new file mode 100644 index 00000000000..439357f5a19 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops-9.config @@ -0,0 +1,2 @@ +-- No imports here +constraints: hashable ==1.4.2.0 diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops.cabal b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops.cabal new file mode 100644 index 00000000000..faddb54ac45 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/oops/oops.cabal @@ -0,0 +1,9 @@ +name: oops +version: 0.1 +license: BSD3 +cabal-version: >= 1.2 +build-type: Simple + +library + exposed-modules: Foo + build-depends: base, hashable diff --git a/cabal-testsuite/PackageTests/ConditionalAndImport/repo/hashable-1.4.2.0/hashable.cabal b/cabal-testsuite/PackageTests/ConditionalAndImport/repo/hashable-1.4.2.0/hashable.cabal new file mode 100644 index 00000000000..de0cf79f7d8 --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/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/ConditionalAndImport/repo/hashable-1.4.3.0/hashable.cabal b/cabal-testsuite/PackageTests/ConditionalAndImport/repo/hashable-1.4.3.0/hashable.cabal new file mode 100644 index 00000000000..b6475a1f15a --- /dev/null +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/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/ConditionalAndImport/same-filename/noncyclical-same-filename-b.config b/cabal-testsuite/PackageTests/ConditionalAndImport/same-filename/noncyclical-same-filename-b.config index dc692490257..09d8f95ef31 100644 --- a/cabal-testsuite/PackageTests/ConditionalAndImport/same-filename/noncyclical-same-filename-b.config +++ b/cabal-testsuite/PackageTests/ConditionalAndImport/same-filename/noncyclical-same-filename-b.config @@ -1 +1 @@ -import: ../noncylical-same-filename-b.config +import: ../noncyclical-same-filename-b.config diff --git a/cabal-testsuite/PackageTests/VersionPriority/0-local.out b/cabal-testsuite/PackageTests/VersionPriority/0-local.out index 309b61103e3..f57e8b4db97 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/0-local.out +++ b/cabal-testsuite/PackageTests/VersionPriority/0-local.out @@ -6,7 +6,9 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /0-local.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config /0-local.project requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 0-local.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from 0-local.project requires ==1.4.3.0) [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) diff --git a/cabal-testsuite/PackageTests/VersionPriority/1-local.out b/cabal-testsuite/PackageTests/VersionPriority/1-local.out index c9aca7097d4..0de3c6d5f1f 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/1-local.out +++ b/cabal-testsuite/PackageTests/VersionPriority/1-local.out @@ -6,8 +6,11 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /1-local-constraints-import.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config stackage-local.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 1-local-constraints-import.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from stackage-local.config requires ==1.4.3.0) + imported by: 1-local-constraints-import.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) # cabal v2-build @@ -16,7 +19,10 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /1-local-import-constraints.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config stackage-local.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 1-local-import-constraints.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from stackage-local.config requires ==1.4.3.0) + imported by: 1-local-import-constraints.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) diff --git a/cabal-testsuite/PackageTests/VersionPriority/1-web.out b/cabal-testsuite/PackageTests/VersionPriority/1-web.out index 9fb08252222..cfdaa0d2dbc 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/1-web.out +++ b/cabal-testsuite/PackageTests/VersionPriority/1-web.out @@ -6,8 +6,11 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /1-web-constraints-import.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 1-web-constraints-import.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) + imported by: 1-web-constraints-import.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) # cabal v2-build @@ -16,7 +19,10 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /1-web-import-constraints.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 1-web-import-constraints.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) + imported by: 1-web-import-constraints.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) diff --git a/cabal-testsuite/PackageTests/VersionPriority/2-local.out b/cabal-testsuite/PackageTests/VersionPriority/2-local.out index cefdd961637..ccb733ca12e 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/2-local.out +++ b/cabal-testsuite/PackageTests/VersionPriority/2-local.out @@ -6,8 +6,12 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /2-local-constraints-import.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config stackage-local.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 2-local-constraints-import.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from stackage-local.config requires ==1.4.3.0) + imported by: hop-local.config + imported by: 2-local-constraints-import.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) # cabal v2-build @@ -16,7 +20,11 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /2-local-import-constraints.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config stackage-local.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 2-local-import-constraints.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from stackage-local.config requires ==1.4.3.0) + imported by: hop-local.config + imported by: 2-local-import-constraints.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) diff --git a/cabal-testsuite/PackageTests/VersionPriority/2-web.out b/cabal-testsuite/PackageTests/VersionPriority/2-web.out index 0b6fd6cf30f..15e5c01517b 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/2-web.out +++ b/cabal-testsuite/PackageTests/VersionPriority/2-web.out @@ -6,8 +6,12 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /2-web-constraints-import.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 2-web-constraints-import.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) + imported by: stackage-web.config + imported by: 2-web-constraints-import.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) # cabal v2-build @@ -16,7 +20,11 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /2-web-import-constraints.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 2-web-import-constraints.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) + imported by: stackage-web.config + imported by: 2-web-import-constraints.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) diff --git a/cabal-testsuite/PackageTests/VersionPriority/3-web.out b/cabal-testsuite/PackageTests/VersionPriority/3-web.out index 13d974b8605..9321613639e 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/3-web.out +++ b/cabal-testsuite/PackageTests/VersionPriority/3-web.out @@ -6,8 +6,13 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /3-web-constraints-import.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 3-web-constraints-import.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) + imported by: stackage-web.config + imported by: hop-web.config + imported by: 3-web-constraints-import.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) # cabal v2-build @@ -16,7 +21,12 @@ Error: [Cabal-7107] Could not resolve dependencies: [__0] trying: cabal-version-override-0.1.0.0 (user goal) [__1] next goal: hashable (dependency of cabal-version-override) -[__1] rejecting: hashable-1.4.3.0 (constraint from project config /3-web-import-constraints.project requires ==1.4.2.0) -[__1] rejecting: hashable-1.4.2.0 (constraint from project config project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) +[__1] rejecting: hashable-1.4.3.0 + (constraint from 3-web-import-constraints.project requires ==1.4.2.0) +[__1] rejecting: hashable-1.4.2.0 + (constraint from project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) + imported by: stackage-web.config + imported by: hop-web.config + imported by: 3-web-import-constraints.project [__1] fail (backjumping, conflict set: cabal-version-override, hashable) After searching the rest of the dependency tree exhaustively, these were the goals I've had most trouble fulfilling: hashable (3), cabal-version-override (2) diff --git a/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.2.0/hashable.cabal b/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.2.0/hashable.cabal index be8d96b783d..de0cf79f7d8 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.2.0/hashable.cabal +++ b/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.2.0/hashable.cabal @@ -1,186 +1,3 @@ cabal-version: 1.12 name: hashable version: 1.4.2.0 -synopsis: A class for types that can be converted to a hash value -description: - This package defines a class, 'Hashable', for types that - can be converted to a hash value. This class - exists for the benefit of hashing-based data - structures. The package provides instances for - basic types and a way to combine hash values. - -homepage: http://github.com/haskell-unordered-containers/hashable - --- SPDX-License-Identifier : BSD-3-Clause -license: BSD3 -license-file: LICENSE -author: - Milan Straka - Johan Tibell - -maintainer: Oleg Grenrus -bug-reports: - https://github.com/haskell-unordered-containers/hashable/issues - -stability: Provisional -category: Data -build-type: Simple -tested-with: - GHC ==8.2.2 - || ==8.4.4 - || ==8.6.5 - || ==8.8.3 - || ==8.10.4 - || ==8.10.7 - || ==9.0.1 - || ==9.0.2 - || ==9.2.5 - || ==9.4.4 - -extra-source-files: - CHANGES.md - include/HsHashable.h - README.md - -flag integer-gmp - description: - Are we using @integer-gmp@ to provide fast Integer instances? No effect on GHC-9.0 or later. - - manual: False - default: True - -flag random-initial-seed - description: - Randomly initialize the initial seed on each final executable invocation - This is useful for catching cases when you rely on (non-existent) - stability of hashable's hash functions. - This is not a security feature. - - manual: True - default: False - -library - exposed-modules: - Data.Hashable - Data.Hashable.Generic - Data.Hashable.Lifted - - other-modules: - Data.Hashable.Class - Data.Hashable.Generic.Instances - Data.Hashable.Imports - Data.Hashable.LowLevel - - c-sources: cbits/fnv.c - include-dirs: include - hs-source-dirs: src - build-depends: - -- REMOVED constraint on base for test - -- base >=4.10.1.0 && <4.18 - base - , bytestring >=0.10.8.2 && <0.12 - , containers >=0.5.10.2 && <0.7 - , deepseq >=1.4.3.0 && <1.5 - , filepath >=1.4.1.2 && <1.5 - , ghc-prim - , text >=1.2.3.0 && <1.3 || >=2.0 && <2.1 - - -- REMOVED conditional compilation pulling in extra dependencies - -- if !impl(ghc >=9.2) - -- build-depends: base-orphans >=0.8.6 && <0.9 - - -- if !impl(ghc >=9.4) - -- build-depends: data-array-byte >=0.1.0.1 && <0.2 - - -- Integer internals - if impl(ghc >=9) - build-depends: ghc-bignum >=1.0 && <1.4 - - if !impl(ghc >=9.0.2) - build-depends: ghc-bignum-orphans >=0.1 && <0.2 - - else - if flag(integer-gmp) - build-depends: integer-gmp >=0.4 && <1.1 - - else - -- this is needed for the automatic flag to be well-balanced - build-depends: integer-simple - - if (flag(random-initial-seed) && impl(ghc)) - cpp-options: -DHASHABLE_RANDOM_SEED=1 - - if os(windows) - c-sources: cbits-win/init.c - - else - c-sources: cbits-unix/init.c - - default-language: Haskell2010 - other-extensions: - BangPatterns - CPP - DeriveDataTypeable - FlexibleContexts - FlexibleInstances - GADTs - KindSignatures - MagicHash - MultiParamTypeClasses - ScopedTypeVariables - Trustworthy - TypeOperators - UnliftedFFITypes - - ghc-options: -Wall -fwarn-tabs - - if impl(ghc >=9.0) - -- these flags may abort compilation with GHC-8.10 - -- https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3295 - ghc-options: -Winferred-safe-imports -Wmissing-safe-haskell-mode - -test-suite hashable-tests - type: exitcode-stdio-1.0 - hs-source-dirs: tests - main-is: Main.hs - other-modules: - Properties - Regress - - build-depends: - base - , bytestring - , ghc-prim - , hashable - , HUnit - , QuickCheck >=2.4.0.1 - , random >=1.0 && <1.3 - , test-framework >=0.3.3 - , test-framework-hunit - , test-framework-quickcheck2 >=0.2.9 - , text >=0.11.0.5 - - if !os(windows) - build-depends: unix - cpp-options: -DHAVE_MMAP - other-modules: Regress.Mmap - other-extensions: CApiFFI - - ghc-options: -Wall -fno-warn-orphans - default-language: Haskell2010 - -test-suite hashable-examples - type: exitcode-stdio-1.0 - build-depends: - base - , ghc-prim - , hashable - - hs-source-dirs: examples - main-is: Main.hs - default-language: Haskell2010 - -source-repository head - type: git - location: - https://github.com/haskell-unordered-containers/hashable.git diff --git a/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.3.0/hashable.cabal b/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.3.0/hashable.cabal index 69efe15c086..b6475a1f15a 100644 --- a/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.3.0/hashable.cabal +++ b/cabal-testsuite/PackageTests/VersionPriority/repo/hashable-1.4.3.0/hashable.cabal @@ -1,188 +1,3 @@ cabal-version: 1.12 name: hashable version: 1.4.3.0 -synopsis: A class for types that can be converted to a hash value -description: - This package defines a class, 'Hashable', for types that - can be converted to a hash value. This class - exists for the benefit of hashing-based data - structures. The package provides instances for - basic types and a way to combine hash values. - . - The 'Hashable' 'hash' values are not guaranteed to be stable across library versions, operating systems or architectures. For stable hashing use named hashes: SHA256, CRC32 etc. - -homepage: http://github.com/haskell-unordered-containers/hashable - --- SPDX-License-Identifier : BSD-3-Clause -license: BSD3 -license-file: LICENSE -author: - Milan Straka - Johan Tibell - -maintainer: Oleg Grenrus -bug-reports: - https://github.com/haskell-unordered-containers/hashable/issues - -stability: Provisional -category: Data -build-type: Simple -tested-with: - GHC ==8.2.2 - || ==8.4.4 - || ==8.6.5 - || ==8.8.3 - || ==8.10.4 - || ==8.10.7 - || ==9.0.1 - || ==9.0.2 - || ==9.2.5 - || ==9.4.4 - || ==9.6.1 - -extra-source-files: - CHANGES.md - include/HsHashable.h - README.md - -flag integer-gmp - description: - Are we using @integer-gmp@ to provide fast Integer instances? No effect on GHC-9.0 or later. - - manual: False - default: True - -flag random-initial-seed - description: - Randomly initialize the initial seed on each final executable invocation - This is useful for catching cases when you rely on (non-existent) - stability of hashable's hash functions. - This is not a security feature. - - manual: True - default: False - -library - exposed-modules: - Data.Hashable - Data.Hashable.Generic - Data.Hashable.Lifted - - other-modules: - Data.Hashable.Class - Data.Hashable.Generic.Instances - Data.Hashable.Imports - Data.Hashable.LowLevel - - c-sources: cbits/fnv.c - include-dirs: include - hs-source-dirs: src - build-depends: - -- REMOVED constraint on base for test - -- base >=4.10.1.0 && <4.19 - base - , bytestring >=0.10.8.2 && <0.12 - , containers >=0.5.10.2 && <0.7 - , deepseq >=1.4.3.0 && <1.5 - , filepath >=1.4.1.2 && <1.5 - , ghc-prim - , text >=1.2.3.0 && <1.3 || >=2.0 && <2.1 - - if !impl(ghc >=9.2) - build-depends: base-orphans >=0.8.6 && <0.10 - - if !impl(ghc >=9.4) - build-depends: data-array-byte >=0.1.0.1 && <0.2 - - -- Integer internals - if impl(ghc >=9) - build-depends: ghc-bignum >=1.0 && <1.4 - - if !impl(ghc >=9.0.2) - build-depends: ghc-bignum-orphans >=0.1 && <0.2 - - else - if flag(integer-gmp) - build-depends: integer-gmp >=0.4 && <1.1 - - else - -- this is needed for the automatic flag to be well-balanced - build-depends: integer-simple - - if (flag(random-initial-seed) && impl(ghc)) - cpp-options: -DHASHABLE_RANDOM_SEED=1 - - if os(windows) - c-sources: cbits-win/init.c - - else - c-sources: cbits-unix/init.c - - default-language: Haskell2010 - other-extensions: - BangPatterns - CPP - DeriveDataTypeable - FlexibleContexts - FlexibleInstances - GADTs - KindSignatures - MagicHash - MultiParamTypeClasses - ScopedTypeVariables - Trustworthy - TypeOperators - UnliftedFFITypes - - ghc-options: -Wall -fwarn-tabs - - if impl(ghc >=9.0) - -- these flags may abort compilation with GHC-8.10 - -- https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3295 - ghc-options: -Winferred-safe-imports -Wmissing-safe-haskell-mode - -test-suite hashable-tests - type: exitcode-stdio-1.0 - hs-source-dirs: tests - main-is: Main.hs - other-modules: - Properties - Regress - - build-depends: - base - , bytestring - , ghc-prim - , hashable - , HUnit - , QuickCheck >=2.4.0.1 - , random >=1.0 && <1.3 - , test-framework >=0.3.3 - , test-framework-hunit - , test-framework-quickcheck2 >=0.2.9 - , text >=0.11.0.5 - - if !os(windows) - build-depends: unix - cpp-options: -DHAVE_MMAP - other-modules: Regress.Mmap - other-extensions: CApiFFI - - ghc-options: -Wall -fno-warn-orphans - default-language: Haskell2010 - -test-suite hashable-examples - type: exitcode-stdio-1.0 - build-depends: - base - , ghc-prim - , hashable - - hs-source-dirs: examples - main-is: Main.hs - default-language: Haskell2010 - -source-repository head - type: git - location: - https://github.com/haskell-unordered-containers/hashable.git diff --git a/changelog.d/issue-9578 b/changelog.d/issue-9578 new file mode 100644 index 00000000000..63913b7f675 --- /dev/null +++ b/changelog.d/issue-9578 @@ -0,0 +1,26 @@ +synopsis: Show provenance of project constraints +description: + Show imports when the solver rejects a package version due to a project + constraint. Even though imports are relative to their parent when imported, + their paths are shown relative to the directory of the project in the solver + output. + + ``` + $ cabal build all --dry-run + ... + [__1] next goal: hashable + [__1] rejecting: hashable-1.4.3.0 + (constraint from cabal.project requires ==1.4.2.0) + [__1] rejecting: hashable-1.4.2.0 + (constraint from project-stackage/nightly-2023-12-07.config requires ==1.4.3.0) + imported by: cabal.project + ``` + + Fixes some test failures detecting cycles in imports, when; + + - the wrong import was reported as starting the cycle + - a cycle was reported that wasn't actually a cycle + +packages: cabal-install-solver cabal-install +prs: #9578 +issues: #9562