1
1
{-# LANGUAGE DeriveGeneric #-}
2
+ {-# LANGUAGE ViewPatterns #-}
2
3
3
4
module Distribution.Solver.Types.ProjectConfigPath
4
5
(
@@ -7,10 +8,11 @@ module Distribution.Solver.Types.ProjectConfigPath
7
8
, projectConfigPathRoot
8
9
, nullProjectConfigPath
9
10
, consProjectConfigPath
11
+ , unconsProjectConfigPath
10
12
11
13
-- * Messages
12
14
, docProjectConfigPath
13
- , docProjectConfigPaths
15
+ , docProjectConfigFiles
14
16
, cyclicalImportMsg
15
17
, docProjectConfigPathFailReason
16
18
@@ -21,17 +23,19 @@ module Distribution.Solver.Types.ProjectConfigPath
21
23
) where
22
24
23
25
import Distribution.Solver.Compat.Prelude hiding (toList , (<>) )
26
+ import qualified Distribution.Solver.Compat.Prelude as P ((<>) )
24
27
import Prelude (sequence )
25
28
26
29
import Data.Coerce (coerce )
27
30
import Data.List.NonEmpty ((<|) )
28
- import Network.URI (parseURI )
31
+ import Network.URI (parseURI , parseAbsoluteURI )
29
32
import System.Directory
30
33
import System.FilePath
31
34
import qualified Data.List.NonEmpty as NE
32
35
import Distribution.Solver.Modular.Version (VR )
33
36
import Distribution.Pretty (prettyShow )
34
37
import Text.PrettyPrint
38
+ import Distribution.Simple.Utils (ordNub )
35
39
36
40
-- | Path to a configuration file, either a singleton project root, or a longer
37
41
-- list representing a path to an import. The path is a non-empty list that we
@@ -45,7 +49,41 @@ import Text.PrettyPrint
45
49
-- List elements are relative to each other but once canonicalized, elements are
46
50
-- relative to the directory of the project root.
47
51
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
49
87
50
88
instance Binary ProjectConfigPath
51
89
instance Structured ProjectConfigPath
@@ -95,15 +133,16 @@ docProjectConfigPath (ProjectConfigPath (p :| ps)) = vcat $
95
133
-- , ProjectConfigPath ("project-cabal/pkgs/integration-tests.config" :| ["project-cabal/pkgs.config","cabal.project"])
96
134
-- , ProjectConfigPath ("project-cabal/pkgs/tests.config" :| ["project-cabal/pkgs.config","cabal.project"])
97
135
-- ]
98
- -- return . render $ docProjectConfigPaths ps
136
+ -- return . render $ docProjectConfigFiles ps
99
137
-- :}
100
138
-- "- 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
+ ]
104
144
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".
107
146
cyclicalImportMsg :: ProjectConfigPath -> Doc
108
147
cyclicalImportMsg path@ (ProjectConfigPath (duplicate :| _)) =
109
148
vcat
@@ -148,6 +187,10 @@ isTopLevelConfigPath (ProjectConfigPath p) = NE.length p == 1
148
187
consProjectConfigPath :: FilePath -> ProjectConfigPath -> ProjectConfigPath
149
188
consProjectConfigPath p ps = ProjectConfigPath (p <| coerce ps)
150
189
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
+
151
194
-- | Make paths relative to the directory of the root of the project, not
152
195
-- relative to the file they were imported from.
153
196
makeRelativeConfigPath :: FilePath -> ProjectConfigPath -> ProjectConfigPath
0 commit comments