Skip to content

Commit 33b19e4

Browse files
authored
Merge pull request #10546 from cabalism/fix/dedup-using-config-from
Deduplicate "using config from" message
2 parents ab54635 + 73a13f1 commit 33b19e4

File tree

28 files changed

+278
-12
lines changed

28 files changed

+278
-12
lines changed

cabal-install-solver/src/Distribution/Solver/Types/ProjectConfigPath.hs

Lines changed: 52 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE DeriveGeneric #-}
2+
{-# LANGUAGE ViewPatterns #-}
23

34
module Distribution.Solver.Types.ProjectConfigPath
45
(
@@ -7,10 +8,11 @@ module Distribution.Solver.Types.ProjectConfigPath
78
, projectConfigPathRoot
89
, nullProjectConfigPath
910
, consProjectConfigPath
11+
, unconsProjectConfigPath
1012

1113
-- * Messages
1214
, docProjectConfigPath
13-
, docProjectConfigPaths
15+
, docProjectConfigFiles
1416
, cyclicalImportMsg
1517
, docProjectConfigPathFailReason
1618

@@ -21,17 +23,19 @@ module Distribution.Solver.Types.ProjectConfigPath
2123
) where
2224

2325
import Distribution.Solver.Compat.Prelude hiding (toList, (<>))
26+
import qualified Distribution.Solver.Compat.Prelude as P ((<>))
2427
import Prelude (sequence)
2528

2629
import Data.Coerce (coerce)
2730
import Data.List.NonEmpty ((<|))
28-
import Network.URI (parseURI)
31+
import Network.URI (parseURI, parseAbsoluteURI)
2932
import System.Directory
3033
import System.FilePath
3134
import qualified Data.List.NonEmpty as NE
3235
import Distribution.Solver.Modular.Version (VR)
3336
import Distribution.Pretty (prettyShow)
3437
import Text.PrettyPrint
38+
import Distribution.Simple.Utils (ordNub)
3539

3640
-- | Path to a configuration file, either a singleton project root, or a longer
3741
-- list representing a path to an import. The path is a non-empty list that we
@@ -45,7 +49,41 @@ import Text.PrettyPrint
4549
-- List elements are relative to each other but once canonicalized, elements are
4650
-- relative to the directory of the project root.
4751
newtype ProjectConfigPath = ProjectConfigPath (NonEmpty FilePath)
48-
deriving (Eq, Ord, Show, Generic)
52+
deriving (Eq, Show, Generic)
53+
54+
-- | Sorts URIs after local file paths and longer file paths after shorter ones
55+
-- as measured by the number of path segments. If still equal, then sorting is
56+
-- lexical.
57+
--
58+
-- The project itself, a single element root path, compared to any of the
59+
-- configuration paths it imports, should always sort first. Comparing one
60+
-- project root path against another is done lexically.
61+
instance Ord ProjectConfigPath where
62+
compare pa@(ProjectConfigPath (NE.toList -> as)) pb@(ProjectConfigPath (NE.toList -> bs)) =
63+
case (as, bs) of
64+
-- There should only ever be one root project path, only one path
65+
-- with length 1. Comparing it to itself should be EQ. Don't assume
66+
-- this though, do a comparison anyway when both sides have length
67+
-- 1. The root path, the project itself, should always be the first
68+
-- path in a sorted listing.
69+
([a], [b]) -> compare a b
70+
([_], _) -> LT
71+
(_, [_]) -> GT
72+
73+
(a:_, b:_) -> case (parseAbsoluteURI a, parseAbsoluteURI b) of
74+
(Just ua, Just ub) -> compare ua ub P.<> compare aImporters bImporters
75+
(Just _, Nothing) -> GT
76+
(Nothing, Just _) -> LT
77+
(Nothing, Nothing) -> compare (splitPath a) (splitPath b) P.<> compare aImporters bImporters
78+
_ ->
79+
compare (length as) (length bs)
80+
P.<> compare (length aPaths) (length bPaths)
81+
P.<> compare aPaths bPaths
82+
where
83+
aPaths = splitPath <$> as
84+
bPaths = splitPath <$> bs
85+
aImporters = snd $ unconsProjectConfigPath pa
86+
bImporters = snd $ unconsProjectConfigPath pb
4987

5088
instance Binary ProjectConfigPath
5189
instance Structured ProjectConfigPath
@@ -95,15 +133,16 @@ docProjectConfigPath (ProjectConfigPath (p :| ps)) = vcat $
95133
-- , ProjectConfigPath ("project-cabal/pkgs/integration-tests.config" :| ["project-cabal/pkgs.config","cabal.project"])
96134
-- , ProjectConfigPath ("project-cabal/pkgs/tests.config" :| ["project-cabal/pkgs.config","cabal.project"])
97135
-- ]
98-
-- return . render $ docProjectConfigPaths ps
136+
-- return . render $ docProjectConfigFiles ps
99137
-- :}
100138
-- "- cabal.project\n- project-cabal/constraints.config\n- project-cabal/ghc-latest.config\n- project-cabal/ghc-options.config\n- project-cabal/pkgs.config\n- project-cabal/pkgs/benchmarks.config\n- project-cabal/pkgs/buildinfo.config\n- project-cabal/pkgs/cabal.config\n- project-cabal/pkgs/install.config\n- project-cabal/pkgs/integration-tests.config\n- project-cabal/pkgs/tests.config"
101-
docProjectConfigPaths :: [ProjectConfigPath] -> Doc
102-
docProjectConfigPaths ps = vcat
103-
[ text "-" <+> text p | ProjectConfigPath (p :| _) <- ps ]
139+
docProjectConfigFiles :: [ProjectConfigPath] -> Doc
140+
docProjectConfigFiles ps = vcat
141+
[ text "-" <+> text p
142+
| p <- ordNub [ p | ProjectConfigPath (p :| _) <- ps ]
143+
]
104144

105-
-- | A message for a cyclical import, assuming the head of the path is the
106-
-- duplicate.
145+
-- | A message for a cyclical import, a "cyclical import of".
107146
cyclicalImportMsg :: ProjectConfigPath -> Doc
108147
cyclicalImportMsg path@(ProjectConfigPath (duplicate :| _)) =
109148
vcat
@@ -148,6 +187,10 @@ isTopLevelConfigPath (ProjectConfigPath p) = NE.length p == 1
148187
consProjectConfigPath :: FilePath -> ProjectConfigPath -> ProjectConfigPath
149188
consProjectConfigPath p ps = ProjectConfigPath (p <| coerce ps)
150189

190+
-- | Split the path into the importee and the importer path.
191+
unconsProjectConfigPath :: ProjectConfigPath -> (FilePath, Maybe ProjectConfigPath)
192+
unconsProjectConfigPath ps = fmap ProjectConfigPath <$> NE.uncons (coerce ps)
193+
151194
-- | Make paths relative to the directory of the root of the project, not
152195
-- relative to the file they were imported from.
153196
makeRelativeConfigPath :: FilePath -> ProjectConfigPath -> ProjectConfigPath

cabal-install/src/Distribution/Client/ProjectConfig.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -951,7 +951,7 @@ renderBadPackageLocations (BadPackageLocations provenance bpls)
951951

952952
renderExplicit =
953953
"When using configuration from:\n"
954-
++ render (nest 2 . docProjectConfigPaths $ mapMaybe getExplicit (Set.toList provenance))
954+
++ render (nest 2 . docProjectConfigFiles $ mapMaybe getExplicit (Set.toList provenance))
955955
++ "\nThe following errors occurred:\n"
956956
++ render (nest 2 $ vcat ((text "-" <+>) . text <$> map renderBadPackageLocation bpls))
957957

cabal-testsuite/PackageTests/ConditionalAndImport/cabal.out

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -67,9 +67,9 @@ cyclical import of cyclical-2-out-out-self-b.config;
6767
# checking that cyclical check doesn't false-positive on same file names in different folders; hoping within a folder and then into a subfolder
6868
# cabal v2-build
6969
Configuration is affected by the following files:
70+
- noncyclical-same-filename-a.project
7071
- noncyclical-same-filename-a.config
7172
imported by: noncyclical-same-filename-a.project
72-
- noncyclical-same-filename-a.project
7373
- same-filename/noncyclical-same-filename-a.config
7474
imported by: noncyclical-same-filename-a.config
7575
imported by: noncyclical-same-filename-a.project
@@ -83,10 +83,10 @@ Building library for my-0.1...
8383
# checking that cyclical check doesn't false-positive on same file names in different folders; hoping into a subfolder and then back out again
8484
# cabal v2-build
8585
Configuration is affected by the following files:
86+
- noncyclical-same-filename-b.project
8687
- noncyclical-same-filename-b.config
8788
imported by: same-filename/noncyclical-same-filename-b.config
8889
imported by: noncyclical-same-filename-b.project
89-
- noncyclical-same-filename-b.project
9090
- same-filename/noncyclical-same-filename-b.config
9191
imported by: noncyclical-same-filename-b.project
9292
Up to date
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
-- WARNING: Override the `with-compiler: ghc-x.y.z` of the stackage import, of
2+
-- https://www.stackage.org/nightly-yyyy-mm-dd/cabal.config. Otherwise tests
3+
-- will fail with:
4+
-- -Error: [Cabal-5490]
5+
-- -Cannot find the program 'ghc'. User-specified path 'ghc-x.y.z' does not
6+
-- refer to an executable and the program is not on the system path.
7+
with-compiler: ghc
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
import: cfg/1.config
2+
import: cfg/3.config
3+
import: cfg/5.config
4+
import: cfg/7.config
5+
import: cfg/9.config
6+
7+
import: with-ghc.config
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
import: cfg/3.config
2+
import: https://www.stackage.org/lts-21.25/cabal.config
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
import: cfg/5.config
2+
import: https://www.stackage.org/lts-21.25/cabal.config
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
import: cfg/7.config
2+
import: https://www.stackage.org/lts-21.25/cabal.config
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
import: cfg/9.config
2+
import: https://www.stackage.org/lts-21.25/cabal.config
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
# checking "using config from message" with URI imports
2+
# cabal v2-build
3+
# checking that package directories and locations are reported in order

0 commit comments

Comments
 (0)