extract findConflictedAlias to Unison.Merge

This commit is contained in:
Mitchell Rosen 2024-08-01 08:03:48 -04:00
parent 9e4719e408
commit 2860665925
7 changed files with 84 additions and 58 deletions

View File

@ -260,8 +260,8 @@ doMerge info = do
-- Bail early if it looks like we can't proceed with the merge, because Alice or Bob has one or more conflicted alias
for_ ((,) <$> Merge.TwoWay mergeTarget mergeSource <*> diffs) \(who, diff) ->
whenJust (findConflictedAlias defns3.lca diff) \(name1, name2) ->
done (Output.MergeConflictedAliases who name1 name2)
whenJust (Merge.findConflictedAlias defns3.lca diff) do
done . Output.MergeConflictedAliases who
-- Combine the LCA->Alice and LCA->Bob diffs together
let diff = Merge.combineDiffs diffs
@ -751,55 +751,6 @@ findTemporaryBranchName projectId mergeSourceAndTarget = do
<> Text.Builder.char '.'
<> Text.Builder.decimal z
-- @findConflictedAlias namespace diff@, given an old namespace and a diff to a new namespace, will return the first
-- "conflicted alias" encountered (if any), where a "conflicted alias" is a pair of names that referred to the same
-- thing in the old namespace, but different things in the new one.
--
-- For example, if the old namespace was
--
-- foo = #foo
-- bar = #foo
--
-- and the new namespace is
--
-- foo = #baz
-- bar = #qux
--
-- then (foo, bar) is a conflicted alias.
--
-- This function currently doesn't return whether the conflicted alias is a decl or a term, but it certainly could.
findConflictedAlias ::
(Ord term, Ord typ) =>
Defns (BiMultimap term Name) (BiMultimap typ Name) ->
DefnsF3 (Map Name) Merge.DiffOp Merge.Synhashed term typ ->
Maybe (Name, Name)
findConflictedAlias defns diff =
asum [go defns.terms diff.terms, go defns.types diff.types]
where
go :: forall ref. (Ord ref) => BiMultimap ref Name -> Map Name (Merge.DiffOp (Merge.Synhashed ref)) -> Maybe (Name, Name)
go namespace diff =
asum (map f (Map.toList diff))
where
f :: (Name, Merge.DiffOp (Merge.Synhashed ref)) -> Maybe (Name, Name)
f (name, op) =
case op of
Merge.DiffOp'Add _ -> Nothing
Merge.DiffOp'Delete _ -> Nothing
Merge.DiffOp'Update hashed1 ->
BiMultimap.lookupPreimage name namespace
& Set.delete name
& Set.toList
& map (g hashed1.new)
& asum
where
g :: Merge.Synhashed ref -> Name -> Maybe (Name, Name)
g hashed1 alias =
case Map.lookup alias diff of
Just (Merge.DiffOp'Update hashed2) | hashed1 == hashed2.new -> Nothing
-- If "foo" was updated but its alias "bar" was deleted, that's ok
Just (Merge.DiffOp'Delete _) -> Nothing
_ -> Just (name, alias)
-- Given a name like "base", try "base__1", then "base__2", etc, until we find a name that doesn't
-- clash with any existing dependencies.
getTwoFreshNames :: Set NameSegment -> NameSegment -> (NameSegment, NameSegment)

View File

@ -420,7 +420,7 @@ data Output
| MergeFailure !FilePath !MergeSourceAndTarget !ProjectBranchName
| MergeSuccess !MergeSourceAndTarget
| MergeSuccessFastForward !MergeSourceAndTarget
| MergeConflictedAliases !MergeSourceOrTarget !Name !Name
| MergeConflictedAliases !MergeSourceOrTarget !(Defn (Name, Name) (Name, Name))
| MergeConflictInvolvingBuiltin !Name
| MergeDefnsInLib !MergeSourceOrTarget
| InstalledLibdep !(ProjectAndBranch ProjectName ProjectBranchName) !NameSegment

View File

@ -1345,17 +1345,24 @@ notifyUser dir = \case
prettyProjectAndBranchName aliceAndBob.alice
<> "was already up-to-date with"
<> P.group (prettyMergeSource aliceAndBob.bob <> ".")
MergeConflictedAliases aliceOrBob name1 name2 ->
MergeConflictedAliases aliceOrBob defn ->
pure $
P.wrap "Sorry, I wasn't able to perform the merge:"
<> P.newline
<> P.newline
<> P.wrap
( "On the merge ancestor,"
<> prettyName name1
<> "and"
<> prettyName name2
<> "were aliases for the same definition, but on"
<> ( let (isTerm, name1, name2) =
case defn of
TermDefn (n1, n2) -> (True, n1, n2)
TypeDefn (n1, n2) -> (False, n1, n2)
in prettyName name1
<> "and"
<> prettyName name2
<> "were aliases for the same"
<> P.group ((if isTerm then "term" else "type") <> ",")
)
<> "but on"
<> prettyMergeSourceOrTarget aliceOrBob
<> "the names have different definitions currently. I'd need just a single new definition to use in their"
<> "dependents when I merge."

View File

@ -15,6 +15,9 @@ module Unison.Merge
oldNameBasedNamespaceDiff,
nameBasedNamespaceDiff,
-- * Finding conflicted aliases
findConflictedAlias,
-- * Combining namespace diffs
CombinedDiffOp (..),
combineDiffs,
@ -55,6 +58,7 @@ import Unison.Merge.Diff (nameBasedNamespaceDiff, oldNameBasedNamespaceDiff)
import Unison.Merge.DiffOp (DiffOp (..))
import Unison.Merge.EitherWay (EitherWay (..))
import Unison.Merge.EitherWayI (EitherWayI (..))
import Unison.Merge.FindConflictedAlias (findConflictedAlias)
import Unison.Merge.Libdeps (LibdepDiffOp (..), applyLibdepsDiff, diffLibdeps)
import Unison.Merge.PartialDeclNameLookup (PartialDeclNameLookup (..))
import Unison.Merge.PartitionCombinedDiffs (partitionCombinedDiffs)

View File

@ -0,0 +1,63 @@
module Unison.Merge.FindConflictedAlias
( findConflictedAlias,
)
where
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Unison.Merge.DiffOp (DiffOp (..))
import Unison.Merge.Synhashed (Synhashed)
import Unison.Merge.Updated qualified
import Unison.Prelude
import Unison.Util.BiMultimap (BiMultimap)
import Unison.Util.BiMultimap qualified as BiMultimap
import Unison.Util.Defn (Defn (..))
import Unison.Util.Defns (Defns (..), DefnsF3)
-- @findConflictedAlias namespace diff@, given an old namespace and a diff to a new namespace, will return the first
-- "conflicted alias" encountered (if any), where a "conflicted alias" is a pair of names that referred to the same
-- thing in the old namespace, but different things in the new one.
--
-- For example, if the old namespace was
--
-- foo = #foo
-- bar = #foo
--
-- and the new namespace is
--
-- foo = #baz
-- bar = #qux
--
-- then (foo, bar) is a conflicted alias.
findConflictedAlias ::
forall name term typ.
(Ord name, Ord term, Ord typ) =>
Defns (BiMultimap term name) (BiMultimap typ name) ->
DefnsF3 (Map name) DiffOp Synhashed term typ ->
Maybe (Defn (name, name) (name, name))
findConflictedAlias defns diff =
asum [TermDefn <$> go defns.terms diff.terms, TypeDefn <$> go defns.types diff.types]
where
go :: forall ref. (Ord ref) => BiMultimap ref name -> Map name (DiffOp (Synhashed ref)) -> Maybe (name, name)
go namespace diff =
asum (map f (Map.toList diff))
where
f :: (name, DiffOp (Synhashed ref)) -> Maybe (name, name)
f (name, op) =
case op of
DiffOp'Add _ -> Nothing
DiffOp'Delete _ -> Nothing
DiffOp'Update hashed1 ->
BiMultimap.lookupPreimage name namespace
& Set.delete name
& Set.toList
& map (g hashed1.new)
& asum
where
g :: Synhashed ref -> name -> Maybe (name, name)
g hashed1 alias =
case Map.lookup alias diff of
Just (DiffOp'Update hashed2) | hashed1 == hashed2.new -> Nothing
-- If "foo" was updated but its alias "bar" was deleted, that's ok
Just (DiffOp'Delete _) -> Nothing
_ -> Just (name, alias)

View File

@ -26,6 +26,7 @@ library
Unison.Merge.DiffOp
Unison.Merge.EitherWay
Unison.Merge.EitherWayI
Unison.Merge.FindConflictedAlias
Unison.Merge.Libdeps
Unison.Merge.PartialDeclNameLookup
Unison.Merge.PartitionCombinedDiffs

View File

@ -1294,7 +1294,7 @@ project/alice> merge /bob
Sorry, I wasn't able to perform the merge:
On the merge ancestor, bar and foo were aliases for the same
definition, but on project/alice the names have different
term, but on project/alice the names have different
definitions currently. I'd need just a single new definition
to use in their dependents when I merge.