[darcs-devel] darcs patch: Make HopefullyPrivate and Cancellation s... (and 20 more)

David Roundy droundy at darcs.net
Mon Sep 17 15:33:52 UTC 2007


On Mon, Sep 17, 2007 at 03:02:52AM +0200, Eric Y. Kow wrote:
> ======================================================================
> Make HopefullyPrivate and Cancellation support gadts
> ======================================================================
> 
> Yay.  Eagerly anticipating the day when I can flip the switch and just
> compile everything with GADTs.

That'll be a while yet.  Several of the interfaces need to be changed in
order for the type witnesses to be propogated throughout.  But I certainly
hope to get there one day!

> > +hokey_merge :: FL Patch C(a b) -> FL Patch C(a c) -> Sealed (FL Patch C(a))
> > +hokey_merge (x:>:xs) p2 | Just (p2':>_) <- commuteFL (invert x :>: NilFL :> p2)
> > +                                        = (x:>:) `mapSeal` hokey_merge xs p2'
> > +                        | otherwise = case conflict_to_end (x :> xs) of
> > +                                      xxs' :> _ -> hokey_merge xxs' p2
> > +hokey_merge NilFL p2 = seal p2
> 
> hokey_merge seems like a slightly hokey name

Well, it's a hokey merge, so it deserves a hokey name!

> > -    Nothing -> impossible
> 
> And I definitely like it when code like this goes away.

Indeed, this has been one of the more satisfying features of the
refactor...   :)

> Here is some more informal documentation along the lines of
> Eric-learns-darcs.  The basic idea behind merging is that given
>   x :> y
>   x :> z       <== you are here
> You want to pull in patch y, adjusting it to fit the new context
>   x :> z :> y' <== you want to be here
> 
> In the simple case (which is the only one I know), the approach consists
> in doing
>   x :> z :> z^
>   x :> z :> z^ :> y 
>   x :> z :> y' :> z^'
>   x :> z :> y'
> 
> We can invert this scenario, starting from the first repository and
> pulling z.  This gives us:
>   x :> y :> y^ :> z
>   x :> y :> z' :> y^'
>   x :> y :> z'
> 
> Nice and symmetrical.  We write this as merge (y :\/: z) = z' :/\: y'

Indeed.

> > +        case actual_merge (y:\/:z) of
> > +        y' -> case commutex (y' :< z) of
> > +                         Nothing -> bugDoc $ text "merge_patches bug"
> > +                                    $$ showPatch y
> > +                                   $$ showPatch z
> > +                                   $$ showPatch y'
> > +                         Just (z' :< _) -> z' :/\: y'
> 
> David seems to say that the same z' can be obtained by commuting the
> original z with the adjusted y'
> 
>   x :> z :> z^
>   x :> z :> z^ :> y 
>   x :> z :> y' :> z^'
>   x :> z :> y'
>   x :> y'' :> z' -- (does y'' always == y?)
> 
> Which makes a sort of intuitive sense... I just wouldn't be able to
> prove it or do anything of the sort.  Note that in any case, this code
> is in an #ifdef and will likely be going away in darcs 2.0.

This isn't quite something we can prove, it's more of an axiom that the
commute must satisfy (that y'' always == y).

> > +  Just (ip2':<p1') -> case commutex (p1' :< p2) of
> > +                      Nothing -> Nothing -- should be a redundant check
> > +                      Just (_:<p1o) -> if really_eq_patches p1o p1
> > +                                       then Just (invert ip2' :/\: p1')
> > +                                       else Nothing
> 
> Also, in some cases, we can obtain z' by just inverting z^' (z^'^ == z').
> 
>   x :> z :> z^
>   x :> z :> z^ :> y 
>   x :> z :> y' :> z^'
>   x :> z :> y'
>   x :> y'' :> z'
>   if (y'' == y) then Just (z^'^ :/\: y')
>                 else Nothing
> 
> Don't really understand what these case are exactly, perhaps the ones
> where (y'' /= y) are ones with conflicts?

No, when y'' /= y, there's a bug somewhere, and we're hiding it by
pretending there was a conflict.  :(

> > +    merge ((x:>:xs) :\/: ys) = fromJust $ do ys' :/\: x' <- return $ mergeFL (x :\/: ys)
> > +                                             xs' :/\: ys'' <- return $ merge (ys' :\/: xs)
> > +                                             return (ys'' :/\: (x' :>: xs'))
> 
> I don't understand why this is not just
>   let ys' :/\: x' = mergeFL (x :\/: ys)
>       xs' :/\: ys'' = merge (ys' :\/: xs)
>   in  (ys'' :/\: (x' :>: xs'))
> 
> Perhaps you're preparing to replace some bits above with actual Maybe
> code?  I haven't really thought about the merge itself, but it seems
> to make sense.

This can't be done with type witnesses in a let block, because it would
cause ghc's brain to explode (because let blocks can include
self-recursion, which do blocks can't).  So it's just a prettier syntax
than nested case statements.

> ======================================================================
> make PatchSet a RL RL.
> ======================================================================
> 
> Clearly the right thing to do.  For the interested, this is part of the
> continuing effort to make more aggressive use of types to prevent us
> from making silly mistakes and to make the code easier to understand.
> 
> > -              | tinfo `elem` deps = (reverse $ (tinfo,thisp) : sofar) : xs'
> > +              | tinfo `elem` deps = (reverseFL $ (tinfo,thisp) :>: sofar) :<: xs'
> 
> Just pointing this out as an example of why we want this.  The new code
> may be a bit harder to read at first, but easier to understand overall
> once you get used to the conventions.
> 
> David:
> 
> I'm trusting you on the FL/RL directions.

They were hard to discover, in some instances, but fortunately, the correct
behavior is self-healing, since the new code doesn't have any way to get
the order wrong... except to insert a reverseFL or reverseRL, which I never
do unless there was already a reverse there in the code.

> Some common patterns, maybe worth putting in Darcs.Patch.Ordered
>  headRL (*)

I'm torn on this one.  I really dislike the idea of defining a partial
function such as head, but it certainly does come up often.  :(

>  concatRL . reverseFL
>  dropWhileNilRL (ok, not common, but maybe worth moving)
>  dropWhileRL

The catch with dropWhileRL is that once we have GADTs throughout the code,
this'll need to change type to a Sealed return type.

>  head . mapRL fst . concatR
>  NilRL :<: NilRL - maybe emptyPatchSet, although that wouldn't be
>                    too useful for pattern matching

Yeah, the pattern matching is the real catch here.

> Also makes me wonder if some sort of List typeclass would be useful for
> us, but we've probably already discussed this.

I'm not sure that I care for the idea of a List typeclass.  I really like
having all the orders very explicitly specified in the code, as I find it
much easier to read.  But then again, what *other* folks find easy to read
might be more to the point...

> (*) headRL could even go into impossible.h so that we get __LINE__ and
>     __FILE__ in the error messages).

I was just going to suggest that, but didn't get around to this.

> > +type PatchSet C(x) = RL (RL PatchInfoAndPatch) C(() y)
> 
> C(() y)? Seems slightly supicious...

Oops, that was meant to be

type PatchSet C(y) = RL (RL PatchInfoAndPatch) C(() y)

but that code isn't yet GADT-clean.

> ======================================================================
> make Named patches a distinct type.
> make SelectPatches be more type-specific.
> ======================================================================
> 
> seems ok
> It's really nice to see all those fromJust's go away

Yes, indeed!

> > +anonymous :: Patch C(x y) -> NamedPatch C(x y)
> > +anonymous p = namepatch "today" "anonymous" "unknown" ["anonymous"] p
> >  infopatch pi p = NamedP pi [] p
> >  adddeps (NamedP pi ds p) ds' = NamedP pi (ds++ds') p
> 
> Would it be useful to have an AnonymousP?

Definitely worth considering... I'd prefer if we could manage to avoid
anonymous patches altogether, which would require yet more refactoring, but
would definitely be cleaner.

> > +    list_touched_files :: p C(x y) -> [FilePath]
> 
> the Commute class seems like a weird place to put this

Yeah, but I couldn't see where else, and it's a useful thing to have that
didn't seem worth defining its own class.

> > hunk ./src/Darcs/Patch/Patchy.lhs 61
> > +    showNicely :: p C(x y) -> Doc
> > +    showNicely = showPatch
> 
> what does Nicely mean?

In the case of named patches, show them in a user-friendly way (e.g. no
brackets around the patch name).

> > +instance (Apply p, ShowPatch p) => ShowPatch (FL p) where
> > +    thing x = thing (helperx x) ++ "s"
> > +        where helperx :: FL a C(x y) -> a C(x y)
> > +              helperx _ = undefined
> 
> eh?

This is just a typesystem hack to get access to the ShowPatch dictionary of
the type we're a list of (which defines "thing").  It's safe, as long as
"thing" doesn't depend on its argument, which it doesn't, for any of our 

> > hunk ./src/Darcs/Repository/DarcsRepo.lhs 183
> > -    where hasChanged :: FilePath -> Patch -> IO Bool
> > -          hasChanged na pa =
> > -             do old <- gzReadFilePS na
> > -                       `catch` (\_ -> return $ packString "")
> > -                case readPatch old of
> > -                  Nothing -> return True -- new patch
> > -                  Just (Sealed oldp,_) -> return $ not (oldp `really_eq_patches` pa)
> 
> Was hasChanged supposed to be some sort of optimisation?
> I'm all for simpler code, so I guess I'm glad to see it go.

Yeah, but I'm not sure it actually optimized anything.  Oh, I know what it
was for:  it was to avoid breaking hard links when we haven't actually
modified the patch file.

> > +readPatchCarefully :: Stringalike s => s -> Maybe (Sealed (Patch C(x)), s)
> > +readPatchCarefully s = case readPatch s of
> > +                       Just (p, s') -> Just (mapSeal patchcontents p, s')
> > +                       _ -> readPatch s
> 
> what does this do?

This reads a patch that may either be a named patch or a plain old patch.
In the former case, it strips the name and just returns the contents.

> > -                        $ filter (is_similar (tp_patch tp) . tp_patch)
> > +                        $ filter ((== touched_files) . list_touched_files . tp_patch)
> 
> does the order of the touched files matter?

That's a good question.  It shouldn't, because I think these are primitive
patches, so there is normally only one touched file.  But it might be worth
sorting them...

> ======================================================================
> remove Cancel/Cancellation/Marked patch types.
> move Conflicted into separate patch type.
> ======================================================================
> 
> Too tired to review these.  As far I as I can see, the bulk of the new
> Darcs.Patch.Conflicted module comes from Darcs.Patch.Commute.
> Conflicted patches come in two flavours, Normal (no conflict) and
> Conflicted (real conflict), sort of like how named patches can be
> anonymous...

Right about the Conflicted module.  It's just factoring out into a single
module and separate type most of Jason's work for the summer.  I plan
(soon) to use it in the conflictor code (which should be started this
week...).
-- 
David Roundy
Department of Physics
Oregon State University
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://lists.osuosl.org/pipermail/darcs-devel/attachments/20070917/eacaf361/attachment.pgp 


More information about the darcs-devel mailing list