[darcs-users] [patch19] Resolve issue1588: add --skip-conflicts option

Petr Rockai me at mornfall.net
Fri Oct 30 00:02:19 UTC 2009


Hi,

Ganesh Sittampalam <ganesh at earth.li> writes:

[snip tool changes, which look OK to me]
[snip import/export/copyright]
> hunk ./src/Darcs/Patch/Permutations.hs 237
>      sloppyIdentity NilRL = IsEq
>      sloppyIdentity (x:<:xs) | IsEq <- sloppyIdentity x = sloppyIdentity xs
>      sloppyIdentity _ = NotEq
> +
> +-- |CommuteFn is the basis of a general framework for building up commutation
> +-- operations between different patch types in a generic manner. Unfortunately
> +-- type classes are not well suited to the problem because of the multiple possible
> +-- routes by which the commuter for (FL p1, FL p2) can be built out of the
> +-- commuter for (p1, p2) - and more complicated problems when we start building
> +-- multiple constructors on top of each other. The type class resolution machinery
> +-- really can't cope with selecting some route, because it doesn't know that all
> +-- possible routes should be equivalent.
> +type CommuteFn p1 p2 = FORALL(x y) (p1 :> p2) C(x y) -> Maybe ((p2 :> p1) C(x y))
> +
> +-- |Build a commuter between a patch and itself using the operation from the type class.
> +selfCommuter :: Commute p => CommuteFn p p
> +selfCommuter = commute
Ok, clear.

> +commuterIdRL :: CommuteFn p1 p2 -> CommuteFn p1 (RL p2)
> +commuterIdRL _ (x :> NilRL) = return (NilRL :> x)
> +commuterIdRL commuter (x :> (y :<: ys))
> +  = do ys' :> x' <- commuterIdRL commuter (x :> ys)
> +       y' :> x'' <- commuter (x' :> y)
> +       return ((y' :<: ys') :> x'')
I always mix up FL and RL (and more importantly their constructors), but
anyway, this should lift a commuter on p1 and p2 to a commuter on p1 (RL p2)
(the type signature says so much). I can't be trusted to understand in which
order an RL is supposed to apply and on which side the end is written, but as
far as I can tell, the function should be correct if the witnesses match up.

Maybe monad is used to propagate commutation failures -- any single failure
fails the whole operation.

> +-- |Partition a list into the patches that commute with the given patch and those that don't (including dependencies)
> +partitionConflictingFL :: (Commute p1, Invert p1) => CommuteFn p1 p2 -> FL p1 C(x y) -> p2 C(x z) -> (FL p1 :> FL p1) C(x y)
> +partitionConflictingFL _ NilFL _ = (NilFL :> NilFL)
> +partitionConflictingFL commuter (x :>: xs) ys =
> +   case commuter (invert x :> ys) of
> +     Nothing -> case commuteWhatWeCanFL (x :> xs) of
> +                 xs_ok :> x' :> xs_deps ->
> +                   case partitionConflictingFL commuter xs_ok ys of
> +                     xs_clean :> xs_conflicts -> xs_clean :> (xs_conflicts +>+ (x' :>: xs_deps))
> +     Just (ys' :> _) ->
> +       case partitionConflictingFL commuter xs ys' of
> +          xs_clean :> xs_conflicts -> (x :>: xs_clean) :> xs_conflicts
It should be probably noted that "ys" is actually treated as an atomic entity,
although its name suggests it is compound (which in practice it is, but that's
probably irrelevant from the POV of this function). We try to commute
inversions of patches in "them" (x :>: xs) past "ys" -- if that works out, all
is good, we copy the commuted inversion into the "clean" portion of the output
and proceed with the rest.

If the commute fails (the Nothing branch), we use commuteWhatWeCanFL to get rid
of the failing "x" and all its dependencies -- tacking them straight into the
"conflicted" part of the output of partitionConflictingFL. We proceed to work
on the part of "them" (i.e. x :>: xs) that does not depend on x.

Overall, it seems right that the patches are partitioned into two FL's, first
for patches whose inverses commute past "ys" and the second for patches that
don't.

Now I just need to figure the inversions...

"ys" is a patch (RL) we have and there are two patches, x :>: y :>: NilFL that
the remote repo has. Now the usual merge could say (it should be symmetric, but
the above seems to use this variant):

common :>: x :>: y :>: invert y :>: invert x :>: ys

and then try to commute ys past the two inversions. So it seems right that we
try to commute past inversions, and we do it in the order in which the merge
would do them (first x then y), so all set and good.

[snip import/export business]

> hunk ./src/Darcs/SelectChanges.hs 653
>             -> (FL p :> FL p) C(x y)
>  tp_patches (x:>y) = mapFL_FL tpPatch x :> mapFL_FL tpPatch y
>  
> +filterOutConflicts :: RepoPatch p
> +                   => [DarcsFlag]
> +                   -> RL (PatchInfoAnd p) C(x r)
> +                   -> Repository p C(r u t)
> +                   -> FL (PatchInfoAnd p) C(x z)
> +                   -> IO (Bool, Sealed (FL (PatchInfoAnd p) C(x)))
> +filterOutConflicts opts us repository them
> +  | SkipConflicts `elem` opts
> +     = do let commuter = commuterIdRL selfCommuter
> +          pend <- fmap n2pia . (anonymous . fromPrims) =<< unrecordedChanges [] repository []
> +          them' :> rest <- return $ partitionConflictingFL commuter them (pend :<: us)
> +          return (check rest, Sealed them')
> +  | otherwise
> +     = return (False, Sealed them)
> +  where check :: FL p C(a b) -> Bool
> +        check NilFL = False
> +        check _ = True
Assuming correctness of partitionConflictingFL, this seems about right. The
"them" patches are commuted, one by one (by partitionConflictingFL) through the
composition of "us" (which ought to be the patches that we have but the remote
repo does not -- in the pull situation) and the unrecorded changes in the
working copy. Any failed commutes there would normally translate to
conflicts. The (commuterIdRL selfCommuter) is used to "atomically" commute a
patch past a the (pend :<: us) sequence -- it's all or nothing, according to
commuteIdRL definition above.

I think the patch is good to go, I'll just run it through testsuite and
witnesses tomorrow out of pure paranoia and then push (bar any objections).

(This is a digression, but: I do think that we could benefit from clearer and
more idiomatic terminology for the patch sequences -- I *think* it works to
imagine an RL as a stack and and FL as a "normal" list... when I was toying
around with these things, it also helped me to actually write RLs with their
head to the right instead to the left as darcs does -- so that patches always
apply from left to right as written in the code, but can be popped/pushed on
different ends, depending on orientation of the list... but I guess this is all
matter of different intuitions...)

Yours,
   Petr.


More information about the darcs-users mailing list