Skip to content

Commit

Permalink
Add Ord instance for ProjectConfigPath
Browse files Browse the repository at this point in the history
- Consider URI in Ord instance
  • Loading branch information
philderbeast committed Nov 12, 2024
1 parent 287d347 commit cb73581
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 2 deletions.
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ViewPatterns #-}

module Distribution.Solver.Types.ProjectConfigPath
(
Expand All @@ -24,7 +25,7 @@ import Prelude (sequence)

import Data.Coerce (coerce)
import Data.List.NonEmpty ((<|))
import Network.URI (parseURI)
import Network.URI (parseURI, parseAbsoluteURI)
import System.Directory
import System.FilePath
import qualified Data.List.NonEmpty as NE
Expand All @@ -44,7 +45,24 @@ import Text.PrettyPrint
-- 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)
deriving (Eq, Show, Generic)

-- | Sorts URIs after local paths and longer paths after shorter ones.
instance Ord ProjectConfigPath where
compare (ProjectConfigPath (NE.toList -> as)) (ProjectConfigPath (NE.toList -> bs)) =
case (as, bs) of
(a:as', b:bs') -> case (parseAbsoluteURI a, parseAbsoluteURI b) of
(Just _, Just _) -> let uriOrd = compare a b in if uriOrd /= EQ then uriOrd else
compare as' bs'
(Just _, Nothing) -> GT
(Nothing, Just _) -> LT
(Nothing, Nothing) -> compare (splitPath a) (splitPath b)
_ -> let lenOrd = compare (length as) (length bs) in if lenOrd /= EQ then lenOrd else
let pathOrd = compare (length ass) (length bss) in if pathOrd /= EQ then pathOrd else
compare ass bss
where
ass = splitPath <$> as
bss = splitPath <$> bs

instance Binary ProjectConfigPath
instance Structured ProjectConfigPath
Expand Down
9 changes: 9 additions & 0 deletions changelog.d/pr-10546
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
---
synopsis: Add an Ord instance for ProjectConfigPath
packages: [cabal-install-solver]
prs: 10546
---

Add an `Ord` instance for `ProjectConfigPath` that sorts URIs after local paths
and longer paths after shorter ones. With this the printing of "Configuration is
affected by the following files" messages is deduplicated.

0 comments on commit cb73581

Please sign in to comment.