DarcsURL: darcs-unstable@darcs.net:screened
MIME-Version: 1.0
Content-Type: multipart/mixed; boundary="=_"
--=_
Content-Type: text/plain; charset="us-ascii"
Content-Transfer-Encoding: quoted-printable
2 patches for repository darcs-unstable@darcs=2Enet:screened:
patch 7610904aa6588a30d42e43d531162b7843fb0fff
Author: Ganesh Sittampalam <ganesh@earth=2Eli>
Date: Tue Sep 3 17:05:38 GMT Summer Time 2019
* WIP: use Prim patches in rebase toedit
patch b333381d224ff0b7edaaddc4da144606d80b3855
Author: Ganesh Sittampalam <ganesh@earth=2Eli>
Date: Tue Sep 3 23:00:35 GMT Summer Time 2019
* HACK: unwind conflicts before suspending
=
This really isn't the right solution because of the way it
constructs multiple ToEdits from a single suspended patch=2E
=
--=_
Content-Type: text/x-darcs-patch; name="patch-preview.txt"
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable
Content-Description: Patch preview
[WIP: use Prim patches in rebase toedit
Ganesh Sittampalam <ganesh@earth=2Eli>**20190903160538
Ignore-this: 93c48344f0ea5dda36817901ce5f8aad
] hunk =2E/harness/Darcs/Test/Patch/Rebase=2Ehs 11
-import Darcs=2EPatch=2EFromPrim
hunk =2E/harness/Darcs/Test/Patch/Rebase=2Ehs 42
- rebase =3D RCFwd (PrimFixup (invert corePrim) :>: NilFL) (fromAnon=
ymousPrim corePrim :>: NilFL)
+ rebase =3D RCFwd (PrimFixup (invert corePrim) :>: NilFL) (corePrim=
:>: NilFL)
hunk =2E/src/Darcs/Patch/Rebase/Container=2Ehs 107
-instance Check p =3D> Check (Suspended p) where
+instance Check (PrimOf p) =3D> Check (Suspended p) where
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 8
- , commuteNamedFixup, commuteFixupNamed, commuteNamedFixups
+ , commuteNamedFixup, commuteFixupNamed
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 17
-import Darcs=2EPatch=2ECommuteFn ( totalCommuterIdFL )
+import Darcs=2EPatch=2ECommuteFn ( totalCommuterIdFL, invertCommuter )
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 22
-import Darcs=2EPatch=2ENamed ( Named(=2E=2E), commuterNamedId, commuterIdN=
amed )
+import Darcs=2EPatch=2ENamed ( Named(=2E=2E), commuterNamedId )
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 27
- , commuteNamedName, commuteNameNamed
+ , commuteNamedName
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 31
- ( FL(=2E=2E), mapFL_FL, (:>)(=2E=2E), (+>+) )
+ ( FL(=2E=2E), mapFL_FL, (:>)(=2E=2E) )
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 108
--- Note that this produces a list result because of the need to use effect=
to
--- extract the result=2E
--- Some general infrastructure for commuting p with PrimOf p would be help=
ful here,
-commuteNamedPrim :: (FromPrim p, Effect p, Commute p)
- =3D> (Named p :> PrimOf p) wX wY
- -> Maybe ((FL (PrimOf p) :> Named p) wX wY)
-commuteNamedPrim (p :> q) =3D do
- q' :> p' <- commuterNamedId selfCommuter (p :> fromAnonymousPrim q)
- return (effect q' :> p')
-
-commutePrimNamed :: (FromPrim p, Effect p, Commute p)
- =3D> (PrimOf p :> Named p) wX wY
- -> Maybe ((Named p :> FL (PrimOf p)) wX wY)
-commutePrimNamed (p :> q) =3D do
- q' :> p' <- commuterIdNamed selfCommuter (fromAnonymousPrim p :> q)
- return (q' :> effect p')
-
-commuteNamedFixup :: (FromPrim p, Effect p, Commute p, Invert p)
- =3D> (Named p :> RebaseFixup p) wX wY
- -> Maybe ((FL (RebaseFixup p) :> Named p) wX wY)
+commuteNamedFixup :: (FromPrim p, Effect p, Commute p, Invert (PrimOf p))
+ =3D> (Named (PrimOf p) :> RebaseFixup p) wX wY
+ -> Maybe ((RebaseFixup p :> Named (PrimOf p)) wX wY)
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 112
- qs' :> p' <- commuteNamedPrim (p :> q)
- return (mapFL_FL PrimFixup qs' :> p')
+ q' :> p' <- commuterNamedId selfCommuter (p :> q)
+ return (PrimFixup q' :> p')
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 116
- return ((NameFixup n' :>: NilFL) :> p')
-
-
-commuteNamedFixups :: (FromPrim p, Effect p, Commute p, Invert p)
- =3D> (Named p :> FL (RebaseFixup p)) wX wY
- -> Maybe ((FL (RebaseFixup p) :> Named p) wX wY)
-commuteNamedFixups (p :> NilFL) =3D return (NilFL :> p)
-commuteNamedFixups (p :> (q :>: rs)) =3D do
- qs' :> p' <- commuteNamedFixup (p :> q)
- rs' :> p'' <- commuteNamedFixups (p' :> rs)
- return ((qs' +>+ rs') :> p'')
-
-
-commuteFixupNamed :: (FromPrim p, Effect p, Commute p, Invert p)
- =3D> (RebaseFixup p :> Named p) wX wY
- -> Maybe ((Named p :> FL (RebaseFixup p)) wX wY)
-commuteFixupNamed (PrimFixup p :> q) =3D do
- q' :> ps' <- commutePrimNamed (p :> q)
- return (q' :> mapFL_FL PrimFixup ps')
-commuteFixupNamed (NameFixup n :> q) =3D do
- q' :> n' <- commuteNameNamed (n :> q)
- return (q' :> (NameFixup n' :>: NilFL))
+ return (NameFixup n' :> p')
+
+commuteFixupNamed :: (FromPrim p, Effect p, Commute p, Invert (PrimOf p))
+ =3D> (RebaseFixup p :> Named (PrimOf p)) wX wY
+ -> Maybe ((Named (PrimOf p) :> RebaseFixup p) wX wY)
+commuteFixupNamed =3D invertCommuter commuteNamedFixup
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 61
--- dependencies as the original patch=2E This is typically
+-- dependencies or content as the original patch=2E This is typically
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 63
+-- Within the rebase state, the patch is stored using prim patches only=2E
+-- Any conflicts should be represented using fixups instead=2E
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 72
- ToEdit :: Named p wX wY -> RebaseItem p wX wY
+ ToEdit :: Named (PrimOf p) wX wY -> RebaseItem p wX wY
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 113
- =3D case commuterIdNamed selfCommuter (fromAnonymousPrim f :> e) of
+ =3D case commuterIdNamed selfCommuter (f :> e) of
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 115
- Just (e' :> f') -> mapSeal (ToEdit e' :>:) (simplifyPushes da (mapF=
L_FL PrimFixup (effect f')) ps)
+ Just (e' :> f') -> mapSeal (ToEdit e' :>:) (simplifyPush da (PrimFi=
xup f') ps)
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 161
- summary (ToEdit p) =3D summary p
+ summary (ToEdit (NamedP _ _ ps)) =3D summary ps
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 178
-instance Check p =3D> Check (RebaseItem p) where
+instance Check (PrimOf p) =3D> Check (RebaseItem p) where
hunk =2E/src/Darcs/Patch/Rebase/Name=2Ehs 153
-commuteNameNamed :: Invert p =3D> CommuteFn (RebaseName p) (Named p)
+commuteNameNamed :: Invert q =3D> CommuteFn (RebaseName p) (Named q)
hunk =2E/src/Darcs/Patch/Rebase/Name=2Ehs 174
-commuteNamedName :: Invert p =3D> CommuteFn (Named p) (RebaseName p)
+commuteNamedName :: Invert p =3D> CommuteFn (Named p) (RebaseName q)
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 26
-import Darcs=2EPatch=2EInfo ( PatchInfo, patchinfo )
+import Darcs=2EPatch=2EInfo ( PatchInfo, patchinfo, displayPatchInfo )
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 51
- , commuteFixupNamed, commuteNamedFixups
+ , commuteFixupNamed, commuteNamedFixup
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 78
- RSFwd :: FL (RebaseFixup p) wX wY -> Named p wY wZ -> RebaseSelect p wX=
wZ
+ RSFwd :: FL (RebaseFixup p) wX wY -> Named (PrimOf p) wY wZ -> RebaseSe=
lect p wX wZ
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 84
- RSRev :: FL (RebaseFixup p) wX wY -> Named p wY wZ -> RebaseSelect p wZ=
wX
+ RSRev :: FL (RebaseFixup p) wX wY -> Named (PrimOf p) wY wZ -> RebaseSe=
lect p wZ wX
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 109
- RCFwd :: FL (RebaseFixup p) wX wY -> FL p wY wZ -> RebaseChange p wX w=
Z
- RCRev :: FL (RebaseFixup p) wX wY -> FL p wY wZ -> RebaseChange p wZ w=
X
+ RCFwd :: FL (RebaseFixup p) wX wY -> FL (PrimOf p) wY wZ -> RebaseChan=
ge p wX wZ
+ RCRev :: FL (RebaseFixup p) wX wY -> FL (PrimOf p) wY wZ -> RebaseChan=
ge p wZ wX
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 129
-rsToPia :: RebaseSelect p wX wY -> Sealed2 (PatchInfoAnd ('RepoType 'NoReb=
ase) p)
+rsToPia :: RebaseSelect p wX wY -> Sealed2 (PatchInfoAnd ('RepoType 'NoReb=
ase) (PrimOf p))
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 163
- case merge (invert (mapFL_FL fromAnonymousPrim prims) :\/: changes=
) of
+ case (merge :: MergeFn (FL p) (FL p))
+ (invert (mapFL_FL fromAnonymousPrim prims)
+ -- TODO changes originates from a Named patch, but
+ -- we don't have access to the name here, so we hav=
e to use
+ -- fromAnonymousPrim=2E Any fake name will be throw=
n away by
+ -- conflictedEffect anyway=2E
+ :\/: (mapFL_FL fromAnonymousPrim changes))
+ of
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 204
- description (RSFwd _ toedit) =3D description toedit
+ description (RSFwd _ (NamedP n _ _)) =3D displayPatchInfo n
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 295
- fixups2' :> edit1' <- commuteNamedFixups (edit1 :> fixups2)
+ fixups2' :> edit1' <- commuterIdFL commuteNamedFixup (edit1 :> fi=
xups2)
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 361
- =3D> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named p)) w=
X wY
- -> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named p) :> F=
L (RebaseFixup p)) wX wY
+ =3D> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named (Prim=
Of p))) wX wY
+ -> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named (PrimOf=
p)) :> FL (RebaseFixup p)) wX wY
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 371
- return (psS' :> (qs' :> te') :> (p''' +>+ ps'))
+ return (psS' :> (qs' :> te') :> (p''' :>: ps'))
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 414
-forceCommutePrim :: (Merge p, Invert p, Effect p, FromPrim p)
- =3D> (PrimOf p :> WDDNamed p) wX wY
- -> (WDDNamed p :> FL (PrimOf p)) wX wY
+forceCommutePrim
+ :: forall p wX wY
+ =2E (Merge p, Invert p, Effect p, FromPrim p)
+ =3D> (PrimOf p :> WDDNamed p) wX wY
+ -> (WDDNamed p :> FL (PrimOf p)) wX wY
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 458
+fromPrimNamed :: FromPrim p =3D> Named (PrimOf p) wX wY -> Named p wX wY
+fromPrimNamed (NamedP n deps ps) =3D NamedP n deps (fromPrims n ps)
+
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 472
- case forceCommutess (fixups :> (WithDroppedDeps toedit [] :>: toed=
its2)) of
+ -- First use 'fromPrimNamed' to change the toedit patch from
+ -- Named (PrimOf p) that we store in the rebase to Named p
+ -- that we store in the repository=2E Then, wrap it in WithDropped=
Deps
+ -- so we can track any explicit dependencies that were lost, and
+ -- finally force-commute the fixups with this and any other patche=
s we are
+ -- unsuspending=2E
+ case forceCommutess
+ (fixups :> (WithDroppedDeps (fromPrimNamed toedit) [] :>: =
toedits2)) of
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 500
- mapFL_FL (noDroppedDeps =2E mkDummy) names +>+ noDroppedDeps t=
oedit :>:
+ mapFL_FL (noDroppedDeps =2E mkDummy) names +>+
+ noDroppedDeps (fromPrimNamed toedit) :>:
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 507
- noDroppedDeps toedit :>:
+ noDroppedDeps (fromPrimNamed toedit) :>:
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 76
-import Darcs=2EPatch=2EPatchInfoAnd ( PatchInfoAnd, info, n2pia, hopefully=
)
-import Darcs=2EPatch=2EFromPrim ( fromAnonymousPrim )
+import Darcs=2EPatch=2EPatchInfoAnd ( PatchInfoAnd, info, n2pia, hopefully=
, fmapFLPIAP )
+import Darcs=2EPatch=2EFromPrim ( PrimOf )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 259
- (Items (mapFL_FL (ToEdit =2E hopefully) psToSuspend +>+ qs))
+ (Items (mapFL_FL (ToEdit =2E hopefully =2E fmapFLPIAP effect) psToSu=
spend +>+ qs))
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 496
- let extractSingle :: FL (RebaseSelect p) wX wY -> (FL (RebaseFixup p) =
:> Named p) wX wY
+ let extractSingle :: FL (RebaseSelect p) wX wY -> (FL (RebaseFixup p) =
:> Named (PrimOf p)) wX wY
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 514
- toeditNew =3D fmapFL_Named (mapFL_FL fromAnonymousPrim =2E canoniz=
eFL da =2E (injects +>+) =2E effect) toedit
+ toeditNew =3D fmapFL_Named (canonizeFL da =2E (injects +>+)) toedi=
t
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 566
- unseal (simplifyPushes da (mapFL=
_FL PrimFixup (effect (patchcontents e)))) =2E
+ unseal (simplifyPushes da (mapFL=
_FL PrimFixup (patchcontents e))) =2E
[HACK: unwind conflicts before suspending
Ganesh Sittampalam <ganesh@earth=2Eli>**20190903220035
Ignore-this: bc49057502fd64faa4bfaa5b983197f0
=
This really isn't the right solution because of the way it
constructs multiple ToEdits from a single suspended patch=2E
=
] hunk =2E/src/Darcs/Patch/Conflict=2Ehs 9
+ , Unwind(=2E=2E)
hunk =2E/src/Darcs/Patch/Conflict=2Ehs 36
+class Unwind p where
+ unwind :: p wX wY -> (FL (PrimOf p) :> PrimOf p :> FL (PrimOf p)) wX wY
+
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 4
- , simplifyPush, simplifyPushes
+ , simplify, simplifyPush, simplifyPushes
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 158
+simplify
+ :: (PrimPatchBase p, Commute p, FromPrim p, Effect p)
+ =3D> D=2EDiffAlgorithm -> FL (RebaseItem p) wX wY -> Sealed (FL (RebaseI=
tem p) wX)
+simplify _ NilFL =3D Sealed NilFL
+simplify da (Fixup f :>: is) =3D unseal (simplifyPush da f) (simplify da i=
s)
+simplify da (ToEdit e :>: is) =3D mapSeal (ToEdit e :>:) (simplify da is)
+
+
hunk =2E/src/Darcs/Patch/RepoPatch=2Ehs 7
-import Darcs=2EPatch=2EConflict ( Conflict )
+import Darcs=2EPatch=2EConflict ( Conflict, Unwind )
hunk =2E/src/Darcs/Patch/RepoPatch=2Ehs 44
+ , Unwind p
hunk =2E/src/Darcs/Patch/V1/Commute=2Ehs 50
-import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail )
+import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail, Unwind )
+import qualified Darcs=2EPatch=2EConflict as Conflict ( Unwind(=2E=2E) )
hunk =2E/src/Darcs/Patch/V1/Commute=2Ehs 78
- FL(=2E=2E), RL(=2E=2E),
+ FL(=2E=2E), RL(=2E=2E), (+>+),
hunk =2E/src/Darcs/Patch/V1/Commute=2Ehs 370
+instance PrimPatch prim =3D> Unwind (RepoPatchV1 prim) where
+ unwind (PP p) =3D NilFL :> p :> NilFL
+ unwind (Merger a b c d) =3D
+ case Conflict=2Eunwind d of
+ ps :> p :> qs ->
+ effect b +>+ effect (invert c) +>+ ps
+ :>
+ p
+ :>
+ qs +>+ invert (effect d) +>+ effect c +>+ effect (invert b) +>+ ef=
fect a
+ unwind (Regrem {}) =3D error "can't unwind a Regrem"
+
hunk =2E/src/Darcs/Patch/V2/RepoPatch=2Ehs 42
-import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail )
+import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail, Unwind(=2E=2E) )
hunk =2E/src/Darcs/Patch/V2/RepoPatch=2Ehs 132
+instance PrimPatch prim =3D> Unwind (RepoPatchV2 prim) where
+ unwind (Normal p) =3D NilFL :> p :> NilFL
+ unwind (Duplicate (Non ps p)) =3D effect ps :> p :> invert p :>: effect =
(invert ps)
+ unwind (Conflictor _ es (Non ps p)) =3D
+ invert es +>+ effect ps
+ :>
+ p
+ :>
+ invert p :>: effect (invert ps)
+ unwind (Etacilpud {}) =3D error "can't unwind an Etacilpud"
+ unwind (InvConflictor {}) =3D error "can't unwind an InvConflictor"
+
hunk =2E/src/Darcs/Patch/V3/Core=2Ehs 73
+instance PrimPatch prim =3D> Unwind (RepoPatchV3 name prim) where
+ unwind (Prim p) =3D NilFL :> wnPatch p :> NilFL
+ unwind (Conflictor (mapFL_FL wnPatch -> es) _ (ctxView -> Sealed ((mapFL=
_FL wnPatch -> cs) :> (wnPatch -> i))))
+ =3D es +>+ cs
+ :>
+ i
+ :>
+ invert i :>: invert cs +>+ NilFL
+ unwind (Rotcilfnoc {}) =3D error "Can't unwind a Rotcilfnoc"
+
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 1
+{-# LANGUAGE ViewPatterns #-}
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 74
-import Darcs=2EPatch=2EInfo ( displayPatchInfo )
+import Darcs=2EPatch=2EConflict ( unwind )
+import Darcs=2EPatch=2EInfo ( displayPatchInfo, PatchInfo, addJunk )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 77
-import Darcs=2EPatch=2ENamed ( Named, fmapFL_Named, patchcontents, patch2p=
atchinfo )
+import Darcs=2EPatch=2ENamed ( Named(=2E=2E), fmapFL_Named, patchcontents,=
patch2patchinfo )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 83
-import Darcs=2EPatch=2ERebase=2EItem ( RebaseItem(=2E=2E), simplifyPush, s=
implifyPushes )
+import Darcs=2EPatch=2ERebase=2EItem ( RebaseItem(=2E=2E), simplify, simpl=
ifyPush, simplifyPushes )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 137
+import System=2EIO=2EUnsafe ( unsafePerformIO )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 261
+ let
+ mkItemsFromRepoPatch :: PatchInfo -> p wA wB -> FL (RebaseItem p) wA=
wB
+ mkItemsFromRepoPatch i (unwind -> fixups1 :> toedit :> fixups2) =3D
+ mapFL_FL (Fixup =2E PrimFixup) fixups1
+ +>+
+ ToEdit (NamedP (newi ()) [] (toedit :>: NilFL))
+ :>:
+ mapFL_FL (Fixup =2E PrimFixup) fixups2
+ where
+ {-# NOINLINE newi #-}
+ newi () =3D unsafePerformIO $ addJunk i
+ mkItems :: PatchInfoAnd ('RepoType 'IsRebase) p wA wB -> FL (RebaseI=
tem p) wA wB
+ mkItems x | False =3D (:>: NilFL) =2E ToEdit =2E hopefully =2E fmapF=
LPIAP effect $ x
+ mkItems x =3D
+ concatFL (mapFL_FL (mkItemsFromRepoPatch (info x)) (patchcontent=
s (hopefully x)))
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 277
- (Items (mapFL_FL (ToEdit =2E hopefully =2E fmapFLPIAP effect) psToSu=
spend +>+ qs))
+ (unseal Items (simplify O=2EMyersDiff (concatFL (mapFL_FL mkItems ps=
ToSuspend) +>+ qs)))
--=_
Content-Type: application/x-darcs-patch; name="wip_-use-prim-patches-in-rebase-toedit.dpatch"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment
Content-Description: A darcs patch for your repository!
New patches:
[WIP: use Prim patches in rebase toedit
Ganesh Sittampalam <ganesh@earth=2Eli>**20190903160538
Ignore-this: 93c48344f0ea5dda36817901ce5f8aad
] hunk =2E/harness/Darcs/Test/Patch/Rebase=2Ehs 11
-import Darcs=2EPatch=2EFromPrim
hunk =2E/harness/Darcs/Test/Patch/Rebase=2Ehs 42
- rebase =3D RCFwd (PrimFixup (invert corePrim) :>: NilFL) (fromAnon=
ymousPrim corePrim :>: NilFL)
+ rebase =3D RCFwd (PrimFixup (invert corePrim) :>: NilFL) (corePrim=
:>: NilFL)
hunk =2E/src/Darcs/Patch/Rebase/Container=2Ehs 107
-instance Check p =3D> Check (Suspended p) where
+instance Check (PrimOf p) =3D> Check (Suspended p) where
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 8
- , commuteNamedFixup, commuteFixupNamed, commuteNamedFixups
+ , commuteNamedFixup, commuteFixupNamed
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 17
-import Darcs=2EPatch=2ECommuteFn ( totalCommuterIdFL )
+import Darcs=2EPatch=2ECommuteFn ( totalCommuterIdFL, invertCommuter )
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 22
-import Darcs=2EPatch=2ENamed ( Named(=2E=2E), commuterNamedId, commuterIdN=
amed )
+import Darcs=2EPatch=2ENamed ( Named(=2E=2E), commuterNamedId )
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 27
- , commuteNamedName, commuteNameNamed
+ , commuteNamedName
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 31
- ( FL(=2E=2E), mapFL_FL, (:>)(=2E=2E), (+>+) )
+ ( FL(=2E=2E), mapFL_FL, (:>)(=2E=2E) )
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 108
--- Note that this produces a list result because of the need to use effect=
to
--- extract the result=2E
--- Some general infrastructure for commuting p with PrimOf p would be help=
ful here,
-commuteNamedPrim :: (FromPrim p, Effect p, Commute p)
- =3D> (Named p :> PrimOf p) wX wY
- -> Maybe ((FL (PrimOf p) :> Named p) wX wY)
-commuteNamedPrim (p :> q) =3D do
- q' :> p' <- commuterNamedId selfCommuter (p :> fromAnonymousPrim q)
- return (effect q' :> p')
-
-commutePrimNamed :: (FromPrim p, Effect p, Commute p)
- =3D> (PrimOf p :> Named p) wX wY
- -> Maybe ((Named p :> FL (PrimOf p)) wX wY)
-commutePrimNamed (p :> q) =3D do
- q' :> p' <- commuterIdNamed selfCommuter (fromAnonymousPrim p :> q)
- return (q' :> effect p')
-
-commuteNamedFixup :: (FromPrim p, Effect p, Commute p, Invert p)
- =3D> (Named p :> RebaseFixup p) wX wY
- -> Maybe ((FL (RebaseFixup p) :> Named p) wX wY)
+commuteNamedFixup :: (FromPrim p, Effect p, Commute p, Invert (PrimOf p))
+ =3D> (Named (PrimOf p) :> RebaseFixup p) wX wY
+ -> Maybe ((RebaseFixup p :> Named (PrimOf p)) wX wY)
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 112
- qs' :> p' <- commuteNamedPrim (p :> q)
- return (mapFL_FL PrimFixup qs' :> p')
+ q' :> p' <- commuterNamedId selfCommuter (p :> q)
+ return (PrimFixup q' :> p')
hunk =2E/src/Darcs/Patch/Rebase/Fixup=2Ehs 116
- return ((NameFixup n' :>: NilFL) :> p')
-
-
-commuteNamedFixups :: (FromPrim p, Effect p, Commute p, Invert p)
- =3D> (Named p :> FL (RebaseFixup p)) wX wY
- -> Maybe ((FL (RebaseFixup p) :> Named p) wX wY)
-commuteNamedFixups (p :> NilFL) =3D return (NilFL :> p)
-commuteNamedFixups (p :> (q :>: rs)) =3D do
- qs' :> p' <- commuteNamedFixup (p :> q)
- rs' :> p'' <- commuteNamedFixups (p' :> rs)
- return ((qs' +>+ rs') :> p'')
-
-
-commuteFixupNamed :: (FromPrim p, Effect p, Commute p, Invert p)
- =3D> (RebaseFixup p :> Named p) wX wY
- -> Maybe ((Named p :> FL (RebaseFixup p)) wX wY)
-commuteFixupNamed (PrimFixup p :> q) =3D do
- q' :> ps' <- commutePrimNamed (p :> q)
- return (q' :> mapFL_FL PrimFixup ps')
-commuteFixupNamed (NameFixup n :> q) =3D do
- q' :> n' <- commuteNameNamed (n :> q)
- return (q' :> (NameFixup n' :>: NilFL))
+ return (NameFixup n' :> p')
+
+commuteFixupNamed :: (FromPrim p, Effect p, Commute p, Invert (PrimOf p))
+ =3D> (RebaseFixup p :> Named (PrimOf p)) wX wY
+ -> Maybe ((Named (PrimOf p) :> RebaseFixup p) wX wY)
+commuteFixupNamed =3D invertCommuter commuteNamedFixup
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 61
--- dependencies as the original patch=2E This is typically
+-- dependencies or content as the original patch=2E This is typically
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 63
+-- Within the rebase state, the patch is stored using prim patches only=2E
+-- Any conflicts should be represented using fixups instead=2E
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 72
- ToEdit :: Named p wX wY -> RebaseItem p wX wY
+ ToEdit :: Named (PrimOf p) wX wY -> RebaseItem p wX wY
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 113
- =3D case commuterIdNamed selfCommuter (fromAnonymousPrim f :> e) of
+ =3D case commuterIdNamed selfCommuter (f :> e) of
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 115
- Just (e' :> f') -> mapSeal (ToEdit e' :>:) (simplifyPushes da (mapF=
L_FL PrimFixup (effect f')) ps)
+ Just (e' :> f') -> mapSeal (ToEdit e' :>:) (simplifyPush da (PrimFi=
xup f') ps)
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 161
- summary (ToEdit p) =3D summary p
+ summary (ToEdit (NamedP _ _ ps)) =3D summary ps
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 178
-instance Check p =3D> Check (RebaseItem p) where
+instance Check (PrimOf p) =3D> Check (RebaseItem p) where
hunk =2E/src/Darcs/Patch/Rebase/Name=2Ehs 153
-commuteNameNamed :: Invert p =3D> CommuteFn (RebaseName p) (Named p)
+commuteNameNamed :: Invert q =3D> CommuteFn (RebaseName p) (Named q)
hunk =2E/src/Darcs/Patch/Rebase/Name=2Ehs 174
-commuteNamedName :: Invert p =3D> CommuteFn (Named p) (RebaseName p)
+commuteNamedName :: Invert p =3D> CommuteFn (Named p) (RebaseName q)
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 26
-import Darcs=2EPatch=2EInfo ( PatchInfo, patchinfo )
+import Darcs=2EPatch=2EInfo ( PatchInfo, patchinfo, displayPatchInfo )
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 51
- , commuteFixupNamed, commuteNamedFixups
+ , commuteFixupNamed, commuteNamedFixup
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 78
- RSFwd :: FL (RebaseFixup p) wX wY -> Named p wY wZ -> RebaseSelect p wX=
wZ
+ RSFwd :: FL (RebaseFixup p) wX wY -> Named (PrimOf p) wY wZ -> RebaseSe=
lect p wX wZ
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 84
- RSRev :: FL (RebaseFixup p) wX wY -> Named p wY wZ -> RebaseSelect p wZ=
wX
+ RSRev :: FL (RebaseFixup p) wX wY -> Named (PrimOf p) wY wZ -> RebaseSe=
lect p wZ wX
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 109
- RCFwd :: FL (RebaseFixup p) wX wY -> FL p wY wZ -> RebaseChange p wX w=
Z
- RCRev :: FL (RebaseFixup p) wX wY -> FL p wY wZ -> RebaseChange p wZ w=
X
+ RCFwd :: FL (RebaseFixup p) wX wY -> FL (PrimOf p) wY wZ -> RebaseChan=
ge p wX wZ
+ RCRev :: FL (RebaseFixup p) wX wY -> FL (PrimOf p) wY wZ -> RebaseChan=
ge p wZ wX
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 129
-rsToPia :: RebaseSelect p wX wY -> Sealed2 (PatchInfoAnd ('RepoType 'NoReb=
ase) p)
+rsToPia :: RebaseSelect p wX wY -> Sealed2 (PatchInfoAnd ('RepoType 'NoReb=
ase) (PrimOf p))
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 163
- case merge (invert (mapFL_FL fromAnonymousPrim prims) :\/: changes=
) of
+ case (merge :: MergeFn (FL p) (FL p))
+ (invert (mapFL_FL fromAnonymousPrim prims)
+ -- TODO changes originates from a Named patch, but
+ -- we don't have access to the name here, so we hav=
e to use
+ -- fromAnonymousPrim=2E Any fake name will be throw=
n away by
+ -- conflictedEffect anyway=2E
+ :\/: (mapFL_FL fromAnonymousPrim changes))
+ of
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 204
- description (RSFwd _ toedit) =3D description toedit
+ description (RSFwd _ (NamedP n _ _)) =3D displayPatchInfo n
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 295
- fixups2' :> edit1' <- commuteNamedFixups (edit1 :> fixups2)
+ fixups2' :> edit1' <- commuterIdFL commuteNamedFixup (edit1 :> fi=
xups2)
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 361
- =3D> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named p)) w=
X wY
- -> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named p) :> F=
L (RebaseFixup p)) wX wY
+ =3D> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named (Prim=
Of p))) wX wY
+ -> (FL (RebaseFixup p) :> (FL (RebaseFixup p) :> Named (PrimOf=
p)) :> FL (RebaseFixup p)) wX wY
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 371
- return (psS' :> (qs' :> te') :> (p''' +>+ ps'))
+ return (psS' :> (qs' :> te') :> (p''' :>: ps'))
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 414
-forceCommutePrim :: (Merge p, Invert p, Effect p, FromPrim p)
- =3D> (PrimOf p :> WDDNamed p) wX wY
- -> (WDDNamed p :> FL (PrimOf p)) wX wY
+forceCommutePrim
+ :: forall p wX wY
+ =2E (Merge p, Invert p, Effect p, FromPrim p)
+ =3D> (PrimOf p :> WDDNamed p) wX wY
+ -> (WDDNamed p :> FL (PrimOf p)) wX wY
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 458
+fromPrimNamed :: FromPrim p =3D> Named (PrimOf p) wX wY -> Named p wX wY
+fromPrimNamed (NamedP n deps ps) =3D NamedP n deps (fromPrims n ps)
+
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 472
- case forceCommutess (fixups :> (WithDroppedDeps toedit [] :>: toed=
its2)) of
+ -- First use 'fromPrimNamed' to change the toedit patch from
+ -- Named (PrimOf p) that we store in the rebase to Named p
+ -- that we store in the repository=2E Then, wrap it in WithDropped=
Deps
+ -- so we can track any explicit dependencies that were lost, and
+ -- finally force-commute the fixups with this and any other patche=
s we are
+ -- unsuspending=2E
+ case forceCommutess
+ (fixups :> (WithDroppedDeps (fromPrimNamed toedit) [] :>: =
toedits2)) of
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 500
- mapFL_FL (noDroppedDeps =2E mkDummy) names +>+ noDroppedDeps t=
oedit :>:
+ mapFL_FL (noDroppedDeps =2E mkDummy) names +>+
+ noDroppedDeps (fromPrimNamed toedit) :>:
hunk =2E/src/Darcs/Patch/Rebase/Viewing=2Ehs 507
- noDroppedDeps toedit :>:
+ noDroppedDeps (fromPrimNamed toedit) :>:
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 76
-import Darcs=2EPatch=2EPatchInfoAnd ( PatchInfoAnd, info, n2pia, hopefully=
)
-import Darcs=2EPatch=2EFromPrim ( fromAnonymousPrim )
+import Darcs=2EPatch=2EPatchInfoAnd ( PatchInfoAnd, info, n2pia, hopefully=
, fmapFLPIAP )
+import Darcs=2EPatch=2EFromPrim ( PrimOf )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 259
- (Items (mapFL_FL (ToEdit =2E hopefully) psToSuspend +>+ qs))
+ (Items (mapFL_FL (ToEdit =2E hopefully =2E fmapFLPIAP effect) psToSu=
spend +>+ qs))
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 496
- let extractSingle :: FL (RebaseSelect p) wX wY -> (FL (RebaseFixup p) =
:> Named p) wX wY
+ let extractSingle :: FL (RebaseSelect p) wX wY -> (FL (RebaseFixup p) =
:> Named (PrimOf p)) wX wY
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 514
- toeditNew =3D fmapFL_Named (mapFL_FL fromAnonymousPrim =2E canoniz=
eFL da =2E (injects +>+) =2E effect) toedit
+ toeditNew =3D fmapFL_Named (canonizeFL da =2E (injects +>+)) toedi=
t
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 566
- unseal (simplifyPushes da (mapFL=
_FL PrimFixup (effect (patchcontents e)))) =2E
+ unseal (simplifyPushes da (mapFL=
_FL PrimFixup (patchcontents e))) =2E
[HACK: unwind conflicts before suspending
Ganesh Sittampalam <ganesh@earth=2Eli>**20190903220035
Ignore-this: bc49057502fd64faa4bfaa5b983197f0
=
This really isn't the right solution because of the way it
constructs multiple ToEdits from a single suspended patch=2E
=
] hunk =2E/src/Darcs/Patch/Conflict=2Ehs 9
+ , Unwind(=2E=2E)
hunk =2E/src/Darcs/Patch/Conflict=2Ehs 36
+class Unwind p where
+ unwind :: p wX wY -> (FL (PrimOf p) :> PrimOf p :> FL (PrimOf p)) wX wY
+
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 4
- , simplifyPush, simplifyPushes
+ , simplify, simplifyPush, simplifyPushes
hunk =2E/src/Darcs/Patch/Rebase/Item=2Ehs 158
+simplify
+ :: (PrimPatchBase p, Commute p, FromPrim p, Effect p)
+ =3D> D=2EDiffAlgorithm -> FL (RebaseItem p) wX wY -> Sealed (FL (RebaseI=
tem p) wX)
+simplify _ NilFL =3D Sealed NilFL
+simplify da (Fixup f :>: is) =3D unseal (simplifyPush da f) (simplify da i=
s)
+simplify da (ToEdit e :>: is) =3D mapSeal (ToEdit e :>:) (simplify da is)
+
+
hunk =2E/src/Darcs/Patch/RepoPatch=2Ehs 7
-import Darcs=2EPatch=2EConflict ( Conflict )
+import Darcs=2EPatch=2EConflict ( Conflict, Unwind )
hunk =2E/src/Darcs/Patch/RepoPatch=2Ehs 44
+ , Unwind p
hunk =2E/src/Darcs/Patch/V1/Commute=2Ehs 50
-import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail )
+import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail, Unwind )
+import qualified Darcs=2EPatch=2EConflict as Conflict ( Unwind(=2E=2E) )
hunk =2E/src/Darcs/Patch/V1/Commute=2Ehs 78
- FL(=2E=2E), RL(=2E=2E),
+ FL(=2E=2E), RL(=2E=2E), (+>+),
hunk =2E/src/Darcs/Patch/V1/Commute=2Ehs 370
+instance PrimPatch prim =3D> Unwind (RepoPatchV1 prim) where
+ unwind (PP p) =3D NilFL :> p :> NilFL
+ unwind (Merger a b c d) =3D
+ case Conflict=2Eunwind d of
+ ps :> p :> qs ->
+ effect b +>+ effect (invert c) +>+ ps
+ :>
+ p
+ :>
+ qs +>+ invert (effect d) +>+ effect c +>+ effect (invert b) +>+ ef=
fect a
+ unwind (Regrem {}) =3D error "can't unwind a Regrem"
+
hunk =2E/src/Darcs/Patch/V2/RepoPatch=2Ehs 42
-import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail )
+import Darcs=2EPatch=2EConflict ( Conflict(=2E=2E), combineConflicts, mang=
leOrFail, Unwind(=2E=2E) )
hunk =2E/src/Darcs/Patch/V2/RepoPatch=2Ehs 132
+instance PrimPatch prim =3D> Unwind (RepoPatchV2 prim) where
+ unwind (Normal p) =3D NilFL :> p :> NilFL
+ unwind (Duplicate (Non ps p)) =3D effect ps :> p :> invert p :>: effect =
(invert ps)
+ unwind (Conflictor _ es (Non ps p)) =3D
+ invert es +>+ effect ps
+ :>
+ p
+ :>
+ invert p :>: effect (invert ps)
+ unwind (Etacilpud {}) =3D error "can't unwind an Etacilpud"
+ unwind (InvConflictor {}) =3D error "can't unwind an InvConflictor"
+
hunk =2E/src/Darcs/Patch/V3/Core=2Ehs 73
+instance PrimPatch prim =3D> Unwind (RepoPatchV3 name prim) where
+ unwind (Prim p) =3D NilFL :> wnPatch p :> NilFL
+ unwind (Conflictor (mapFL_FL wnPatch -> es) _ (ctxView -> Sealed ((mapFL=
_FL wnPatch -> cs) :> (wnPatch -> i))))
+ =3D es +>+ cs
+ :>
+ i
+ :>
+ invert i :>: invert cs +>+ NilFL
+ unwind (Rotcilfnoc {}) =3D error "Can't unwind a Rotcilfnoc"
+
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 1
+{-# LANGUAGE ViewPatterns #-}
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 74
-import Darcs=2EPatch=2EInfo ( displayPatchInfo )
+import Darcs=2EPatch=2EConflict ( unwind )
+import Darcs=2EPatch=2EInfo ( displayPatchInfo, PatchInfo, addJunk )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 77
-import Darcs=2EPatch=2ENamed ( Named, fmapFL_Named, patchcontents, patch2p=
atchinfo )
+import Darcs=2EPatch=2ENamed ( Named(=2E=2E), fmapFL_Named, patchcontents,=
patch2patchinfo )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 83
-import Darcs=2EPatch=2ERebase=2EItem ( RebaseItem(=2E=2E), simplifyPush, s=
implifyPushes )
+import Darcs=2EPatch=2ERebase=2EItem ( RebaseItem(=2E=2E), simplify, simpl=
ifyPush, simplifyPushes )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 137
+import System=2EIO=2EUnsafe ( unsafePerformIO )
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 261
+ let
+ mkItemsFromRepoPatch :: PatchInfo -> p wA wB -> FL (RebaseItem p) wA=
wB
+ mkItemsFromRepoPatch i (unwind -> fixups1 :> toedit :> fixups2) =3D
+ mapFL_FL (Fixup =2E PrimFixup) fixups1
+ +>+
+ ToEdit (NamedP (newi ()) [] (toedit :>: NilFL))
+ :>:
+ mapFL_FL (Fixup =2E PrimFixup) fixups2
+ where
+ {-# NOINLINE newi #-}
+ newi () =3D unsafePerformIO $ addJunk i
+ mkItems :: PatchInfoAnd ('RepoType 'IsRebase) p wA wB -> FL (RebaseI=
tem p) wA wB
+ mkItems x | False =3D (:>: NilFL) =2E ToEdit =2E hopefully =2E fmapF=
LPIAP effect $ x
+ mkItems x =3D
+ concatFL (mapFL_FL (mkItemsFromRepoPatch (info x)) (patchcontent=
s (hopefully x)))
hunk =2E/src/Darcs/UI/Commands/Rebase=2Ehs 277
- (Items (mapFL_FL (ToEdit =2E hopefully =2E fmapFLPIAP effect) psToSu=
spend +>+ qs))
+ (unseal Items (simplify O=2EMyersDiff (concatFL (mapFL_FL mkItems ps=
ToSuspend) +>+ qs)))
Context:
[simplify instance Summary RebaseChange
Ganesh Sittampalam <ganesh@earth=2Eli>**20190903140534
Ignore-this: a5f0306c4213dcd701fb993f54e92e84
=
I'm not sure why it was so complicated before=2E Perhaps
changeAsMerge was used elsewhere at some point=2E
=
Also removed the comment about resolveConflicts which
doesn't make much sense now=2E
=
] =
[make D=2EP=2EV3=2ECore independent of PrimPatchId/Prim=2ENamed
Ganesh Sittampalam <ganesh@earth=2Eli>**20190902092525
Ignore-this: a782b2b5850976e382cf6f1f22af60c0
=
This involves moving the FromPrim instance to V3=2Ehs and
generalising the pattern synonyms used by the test harness=2E
=
We now expose the constructors of RepoPatchV3 from D=2EP=2EV3=2ECore
(but not from D=2EP=2EV3, which is the intended external interface)=2E
=
] =
[turn RepoPatch into a constraint synonym
Ben Franksen <ben=2Efranksen@online=2Ede>**20190829162443
Ignore-this: 3925585e444f26e1b238e5a0df41e6aad5e9983bcce38194d0f8eb5c4bd63=
98ebed934ce6e95ffec
=
This has a lot of advantages wrt maintenance and gets us rid of a few orph=
an
instances=2E Also included a few minor cleanups in Darcs=2EPatch=2ERepoPat=
ch=2E
] =
[introduce PrimWithName and make NamedPrim a type synonym
Ganesh Sittampalam <ganesh@earth=2Eli>**20190827114448
Ignore-this: 934632425eaa3bc82e5769dbee7549a9
] =
[Refactor the commute implementation for NamedPrims
Ganesh Sittampalam <ganesh@earth=2Eli>**20190827113620
Ignore-this: b1aabe8d5b3340a8a65a636460710dd8
=
It now just relies on the Ident class instead of the internals=2E
This also distinguishes a case that ought to be an internal error,
but the unit tests seem to rely on it, so this is left as a
TODO for now=2E
] =
[use Darcs=2EUtil=2EGraph=2Ecomponents for RepoPatchV3
Ben Franksen <ben=2Efranksen@online=2Ede>**20190825211920
Ignore-this: a6991e94f26b09f302c3a51ea09171f8fa09c9c73caa3f701f752f00c76c8=
274761a2dd0bdbe3d86
=
This required a few refactors and the introduction of a new data type for
components=2E In particular, the ltmis algorithm needs to be adapted to
working with just a subset of the vertices of a graph=2E
] =
[move functions to generate graphs from harness to library
Ben Franksen <ben=2Efranksen@online=2Ede>**20190825162321
Ignore-this: b31586463112c753be6a0112b555f7b7f848cc5c39470ede7701a94f2268d=
021c1000a45e0b093a5
] =
[simplify and improve Darcs=2EUtil=2EGraph=2Ecomponents
Ben Franksen <ben=2Efranksen@online=2Ede>**20190825162606
Ignore-this: ed2245de76947994d2a937643fb3d6c406968d7c31f779733504ed605eb15=
302c6dc1a3703427567
=
It wasn't incorrect (according to the spec) but it did not always return
vertices ordered and also did a bit too much work=2E
] =
[add Darcs=2EUtil=2EGraph=2Ecomponents with properties and tests
Ben Franksen <ben=2Efranksen@online=2Ede>**20190825123434
Ignore-this: 3d7e63f134e3528d7d1d64973bc32fb8bbd6d5ba174423d72cd2bc34e0225=
1119394633179e0fa59
] =
[remove Darcs=2EUtil=2EGraph=2Ebk and some minor refactors
Ben Franksen <ben=2Efranksen@online=2Ede>**20190825123225
Ignore-this: b3e8e66874b3692e2f417ba3c877d9573b6fc8b39507b1d28aacd80a087cd=
35705c524039ac64731
] =
[replace quickcheck with leancheck for testing Graph properties
Ben Franksen <ben=2Efranksen@online=2Ede>**20190825133104
Ignore-this: 6ef50b2fd5c131b28df5584f650b525b1e8ed1c5af17dc0a6c0ff4ecfb110=
22c3286e182fc8fffcd
=
Calculating graph properties scales very badly because the specifications
aren't optimised (naturally)=2E Exhaustive testing with leancheck is a lot
more effective here because we avoid testing with (too) large graphs=2E
Unfortunately test-framework is a bit limited in that it doesn't allow to
scale the number of tests, just to set them to a fixed value=2E We opt to
set it to 0x8000 which covers all graphs up to size 6=2E
] =
[Darcs=2EUtil=2EGraph: add properties and test them
Ben Franksen <ben=2Efranksen@online=2Ede>**20190821104132
Ignore-this: 51c2f7127ec6bf9366b0afc8a5aee83e602505c16a12d9d69623369cff583=
65cccef73d31b3bd3b5
] =
[Darcs=2EUtil=2EGraph: add hadocks
Ben Franksen <ben=2Efranksen@online=2Ede>**20190821084048
Ignore-this: 7b7931bdd919da44e34ae60340f446783e1b5343dfe3aeca2b241d4b1ee25=
c7e514c35907bdc60ca
] =
[Darcs=2EUtil=2EGraph: make helper functions local to ltmis
Ben Franksen <ben=2Efranksen@online=2Ede>**20190821083917
Ignore-this: 7869236b4f6e283050b2195f54c2465091194278a9b32f210de5c6cb24b2a=
2f11b1f8b2a402084c6
] =
[fix layout in parts of D=2EP=2ERebase=2EViewing and D=2EUI=2ECommands=2ERe=
base
Ben Franksen <ben=2Efranksen@online=2Ede>**20190802172459
Ignore-this: 87f5e93e3f3d78674867cc8866f30fa2e5e5be889100c5a3b897f78f04e9a=
09051086fc611176427
=
This is to avoid extremely long code lines=2E
] =
[regard explicit dependencies as resolving conflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20190720115158
Ignore-this: 736f3f54fc3b8b6c62890b1b1026e9f095168ef3a5499b975cb94c10a0a38=
019e619f2a24620ea20
=
This is necessary to allow users to resolve a conlfict in favour of what
darcs does by default (i=2Ee=2E apply neither of the conflicting changes)=
=2E The
implementation is mostly in Darcs=2EPatch=2ENamed which now has an instanc=
e
Conflict=2E The PatchInfoAnd instance only delegates to the contained Name=
d =
patch=2E A subtlety here is that for efficiency and correctness in the fac=
e of
lazy repos, we must make sure that hopefully is lazy in its patch argument=
=2E
] =
[resolve issue2550: apply only properly mangled resolutions, warn about any=
others
Ben Franksen <ben=2Efranksen@online=2Ede>**20190716193444
Ignore-this: f63dd3fe64a45fde5ce550734183b63968e968390625870fbd2bb944f87ed=
e1cea563a6ab84c34f8
=
To support this change we add the new data type StandardResolution and
return that from standardResolution=2E It contains a summary of the data w=
e
gathered from calling resolveConflicts: the mangled resolutions, merged in=
to
a single FL, the list of conflicted paths, and an IO action to warn about
and display any (unravelled) conflicts that we couldn't properly mangle=2E=
The
warning is normally only displayed if we actually want mangling to happen
i=2Ee=2E if --mark-conflicts is in effect (except for the mark-conflicts c=
ommand)=2E
] =
[pass a PrimCanonize dictionary explicitly when needed
Ganesh Sittampalam <ganesh@earth=2Eli>**20190812142441
Ignore-this: 377a198414a29a79b2fee197920a5cab
=
This allows us to get rid of the dummy instance for
PrimCanonize (NamedPrim prim)
=
] =
[use new TestablePrim alias in the harness instead of PrimPatch
Ganesh Sittampalam <ganesh@earth=2Eli>**20190812141315
Ignore-this: c9ab451d95db338f8e9ff6c3a57364ef
=
This allows the removal of a bunch of dummy instances for NamedPrim
=
] =
[improve doc comments for Rotcilfnoc
Ganesh Sittampalam <ganesh@earth=2Eli>**20190811165258
Ignore-this: 35c95b9e7ce666ebe2d48ac6736775d
] =
[clean up the Matchable mess
Ben Franksen <ben=2Efranksen@online=2Ede>**20190812152453
Ignore-this: c80c99da5e05957f138ce0fc802aff931e64ba4d7b7f79d39623a86c8360f=
7e53123f8a93bf4718a
=
This is a large refactor=2E Matchable is no longer a class but a constrain=
t
synonym=2E This means we don't have to define instances and can therefore
defined it in Darcs=2EPatch=2EMatch=2E Darcs=2EPatch=2EMatchable has been =
deleted=2E
=
MatchFun, Matcher, and PatchSetMatch no longer get the patch type or repo
type as parameter=2E Instead, MatchFun is now a data type that contains th=
e
polymorphic match function (constrained to work only on Matchable patches)=
=2E
=
Matchable p now also requires Ident p and PatchId p ~ PatchInfo, so we hav=
e
access to the PatchInfo (using ident)=2E The goal here was to generalize
matching functions from PatchInfoAnd to any Matchable patch type=2E Since =
some
of the matching functions work on PatchSets, which have PatchInfoAnd
hard-coded, we add a new constraint synonym for RepoPatches p such that
PatchInfoAnd rt p becomes Matchable=2E
=
Darcs=2EUI=2ESelectPatches no longer has PatchInfoAnd in any of its type
signatures=2E
] =
[replace some undefineds with TypeApplications
Ganesh Sittampalam <ganesh@earth=2Eli>**20190812134126
Ignore-this: 67ab11c1b41ff8ffca3027493ebc923b
] =
[replace commenting out with if False in qc_V1P1
Ganesh Sittampalam <ganesh@earth=2Eli>**20190812133057
Ignore-this: 807001bd1d8c8d8ddce51135e7d598a1
=
Predictably the code had rotted a bit, but it looks like
from history that commute_properties is now pair_properties
] =
[add V3INTEGRATION comments about the NamedPrim representation
Ganesh Sittampalam <ganesh@earth=2Eli>**20190809153535
Ignore-this: 2312bd732fdc7a1e6868dfc732c8fb45
] =
[use the old test case generator for most RepoPatchV2 properties
Ben Franksen <ben=2Efranksen@online=2Ede>**20190801211751
Ignore-this: 1078a32e6e47edba95e4595ebe3db99f76c4203ef2a74c9e9360d7cf9393b=
8165622ddfd26f3b6da
=
With the new test case generator many properties fail for RepoPatchV2, so =
we
go back to the simpler generator that does not record patches after
conflicts=2E This required re-adding merge_properties and also adds
triple_properties (for permutivity)=2E While we're at it, also test the
triple_properties for prim patches=2E
] =
[harness: simplify type signatures and superclass constraints
Ben Franksen <ben=2Efranksen@online=2Ede>**20190717152157
Ignore-this: 8bc80efd13a66a248f82571add8a91d8828340395f600dc0e2a09a148aca3=
4706ad93a05eb410a39
] =
[harness: add propConsistentReorderings and test it
Ben Franksen <ben=2Efranksen@online=2Ede>**20190717152018
Ignore-this: 5320df5208bfb482142ecc6768dcecce8c5c756c86e1caa4e3d2a6fb0b068=
90cf78a904d617bbaf2
=
This property is similar to propConsistentTreeFlattenings but takes an RL
RepoPatch and a start state as input=2E This allows us to test it more
thoroughly by using the new test case generator for RL RepoPatch=2E
] =
[harness: simplify constraints in D=2ET=2EPatch
Ben Franksen <ben=2Efranksen@online=2Ede>**20190716174132
Ignore-this: b974317bad52331d8edb4091e4ed727f5b52092f04c6a114a5f62338a1f91=
d04c24c64b781975f5c
] =
[use TestOnly for the constructors of RepoPatchV3
Ganesh Sittampalam <ganesh@earth=2Eli>**20190809182248
Ignore-this: 6a51e1baadcad20103eb191863197b7d
] =
[eliminate spurious superclass constraint Eq2 p =3D> Ident p
Ben Franksen <ben=2Efranksen@online=2Ede>**20190729130835
Ignore-this: 93bce7a66ca3d4fc31228dd955c54dee71e2c81bc9be09f6cd2946a61d305=
c6c6a74336b5dcb362
=
This change allows us to remove /lots/ of unneeded Eq2 constraints, and
consequently a number of Eq2 instances under Darcs=2EPatch=2ERebase=2E
] =
[refactor withSelectedPatchFromRepo
Ben Franksen <ben=2Efranksen@online=2Ede>**20190719081252
Ignore-this: 768bed4a27cfd0079d7e9d281c71c94515c16a93227297f39b4422061aa8c=
507b7876fd7789973fb
=
It now gets an RL of patches instead of a Repository=2E At the place of us=
e in
the amend command we do the readRepo and patchSet2RL ourselves=2E This
prepares for adding --not-in-remote option to amend but makes sense
independently=2E
] =
[colorize warnings
Ben Franksen <ben=2Efranksen@online=2Ede>**20190711162535
Ignore-this: d9d0a17896588a7132e5e18ab6702a8e122ddb8c57b7beda0f99c8de86907=
ed59d50810520fdbc1e
] =
[demote errors in defaults file and commandline to warnings
Ben Franksen <ben=2Efranksen@online=2Ede>**20190705213001
Ignore-this: 4fda8b31bb458925104e60ddacade991dab423840242a377b5ed928779dd1=
f8fe1cc9ed536fdc4dd
=
When we change the UI by e=2Eg=2E adding a new command line option, we wan=
t the
user to be able to use these switches in their defaults file without this
giving an error when they use an older version of darcs=2E So this change
improves forwards compatibility=2E
] =
[some code cleanups for unsuspendCmd
Ben Franksen <ben=2Efranksen@online=2Ede>**20190713092534
Ignore-this: 3c48c309d9d772434ba1b8a4533c6da0b62460b1f1dee1483c3c182539ded=
ee919510a435621f61a
=
This factors out the check that there are no unrecorded changes into a loc=
al
procedure that returns a Repository with new witnesses if successful, or
else dies=2E We also pass the command name to 'unsuspendCmd' to improve th=
e
error message for the reify command and remove a number of pattern type
signatures that are no longer needed=2E
] =
[add 2 TODO items with V3INTEGRATION tag to Darcs=2EUtil=2EGraph
Ben Franksen <ben=2Efranksen@online=2Ede>**20190716172454
Ignore-this: 42a7aa4a7aa59224b09211911858c52ebbf9ff7035c39156d2e19367f3880=
519763b9663c8399fcc
] =
[clean up imports in two modules
Ben Franksen <ben=2Efranksen@online=2Ede>**20190714114534
Ignore-this: c6baa1d94e49f44c563741c974ccdc42e98148c7641ee3c3c4cd4c7f4db10=
ffa3983acb9c19a03fc
] =
[introduce type synonyms Mangled and Unravelled
Ben Franksen <ben=2Efranksen@online=2Ede>**20190712201605
Ignore-this: 56a50f819d1dbfb2143d6ddc490cebd98e93ad8f9e655c77e61e6d6dfbc0a=
3575a3fb1ef1ecda75a
] =
[change the return type of mangleUnravelled
Ben Franksen <ben=2Efranksen@online=2Ede>**20190712194311
Ignore-this: 7c8143c71ca601b1e32ccce142fd40fabf99e268c3fd8063212ff1b63a60b=
f1bdff7a426fd698698
=
This makes it clear that mangleUnravelled is unable to deal with conflicts
involving anything other than hunks=2E Previously we returned the unmodifi=
ed
head of the input list if that was the case, now we return Nothing=2E
] =
[add an explicit type for the output of resolveConflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20190712194303
Ignore-this: b595de1e35192407f2a162f8a3e525fb19bc9bf15527bbcd999589260929c=
0729d54e05762014db3
=
This makes it clear that the output contains first the
'mangled' view followed by all the conflicting parts=2E
Currently the mangled view is the conflict markers if
the conflict is all hunks, and one of the conflicting
parts if not=2E
] =
[cleanup and refactor mangleUnravelled
Ben Franksen <ben=2Efranksen@online=2Ede>**20190712182656
Ignore-this: 58ee0b078c09f1f163de3626ef806869e03ec528ddd54c5e361dde62ac88c=
6e981d04eb6b67d4e53
] =
[move instance PrimMangleUnravelled for Prim=2EV1 to its own module
Ben Franksen <ben=2Efranksen@online=2Ede>**20190712172529
Ignore-this: 47695726193eddf3990a3f3ff1e48c57c8ced7fc355928c84a39ad9c2bc0a=
1c82ba9a22165014b00
=
This is a pure code move without any changes to the definitions=2E It serv=
es
as preparation for a larger refactor but makes sense in its own right=2E
] =
[harness: test prop_ctxEq
Ben Franksen <ben=2Efranksen@online=2Ede>**20190716200452
Ignore-this: 5748801a2bf402fd13c56c729685681410c9c09169633d3314ee257e6bf0a=
ceaeb2b4d31ab17ff5d
] =
[fix v3 repo property prop_conflictsCommutePastConflictor
Ben Franksen <ben=2Efranksen@online=2Ede>**20190716153400
Ignore-this: af00b2159f3c691dbd903e510ae1240fe6e6be6bf4f4d5773dd8260e97b01=
42f352ad0b822e938e
=
The property as stated before didn't take conflict resolutions into accoun=
t,
that is, parts of a conflict could be resolved by recording a patch that
depends on that part=2E In this case we can only commute the conflicted pa=
rt
past the conflictor if we drag the resolution with us=2E
] =
[add two properties about conflict resolution and test them
Ben Franksen <ben=2Efranksen@online=2Ede>**20190710174341
Ignore-this: 3420413c7b20f8cee14c3c68b96b18f1638a20dd7136898191f8768cef03f=
5f9bfbf4dd525ea5494
=
This required adding a utility function permutationsRL and factoring out
mergeList from D=2ER=2EResolution into D=2EP=2ECommuteNoConflicts=2E
] =
[v3: add an important conflictor property
Ben Franksen <ben=2Efranksen@online=2Ede>**20190624101201
Ignore-this: 1a3903fa83494eca84415faba474a6669aeaba0bf3a2e5d82079b01b4eed8=
11a96e19372ca388f2b
] =
[turn fancyPrinters into an IO action
Ben Franksen <ben=2Efranksen@online=2Ede>**20190619200647
Ignore-this: e7e31c16555e928c1408ffafd8c6ad8f5144efc3e7cc58d70ebf67307ade9=
45e41b900ac4535e116
=
This is what it actually is, via getPolicy=2E The unsafePerformIO was
perfunctory, since fancyPrinters (almost) always gets passed to a real IO
action that does the actual printing=2E The only exceptions are when we us=
e it
for tracing and in the harness when converting our TestResult to HUnit or
QuickCheck=2E Consequently showDoc has been renamed unsafeRenderStringColo=
red
(to discourage its use) and a function debugDoc added=2E
] =
[refactor the interface for creating Named patches from prims
Ben Franksen <ben=2Efranksen@online=2Ede>**20190714091935
Ignore-this: bb7f0bd1f451d6f0a01cab219dabc57dc5ac0eb3258a2828a5eae49b750b1=
5aa591526ffcc26de30
=
This uncouples the type family PatchId from class Ident, so we can use it
for patch types that have no instance Ident=2E This allows us to change th=
e
type of method fromPrim to receive a 'PatchId p' instead of the raw
ingredients of a PrimPatchId=2E We add method fromPrims so we can delegate
generating prim patch ids to the implementation of the RepoPatch type=2E T=
he
default method definitions for fromPrim and fromPrims ignore their input, =
so
we don't even have to create dummy type instances for PatchId=2E
=
We add the function positivePrimPatchIds to the interface of NamedPrim to
support implementation of fromPrims for RepoPatchV3=2E This hides the seri=
al
numbers from client code which are now an implementation detail of
NamedPrim=2E The function takes a PatchInfo as input, so the fact that we =
use
the hash of the PatchInfo underneath is now also an implementation detail=
=2E A
single exception is made with unsafePrimPatchId which we need (only) in th=
e
harness to define an instance Arbitrary=2E
] =
[v3: fix and restructure conflict resolution
Ben Franksen <ben=2Efranksen@online=2Ede>**20190710211725
Ignore-this: 648fc16081d495f7067b6e2a3b7d42f905bb29a7053ee952447bb1e3023e1=
034a6fc651c00330f79
=
It probably doesn't make much sense to view the diffs here, since I really
restructured things a lot, re-wrote the documentation comments, and rename=
d
and reordered functions=2E
=
The main semantic changes are:
- fixed the 'components' function which was buggy
- fixed and cleaned up the history traversal to find vertices
- throw out the no longer needed 'dropDominated'
- calculate conflicts between vertices freshly
=
The last point was crucial=2E In my original version I made the mistake to
think that we can read off conflicts between vertices, i=2Ee=2E contexted =
prims,
directly from the conflictor=2E This is only so in the simplest case of tw=
o
conflicting prims=2E In general it is false: the contexted patch represent=
ed
by a conflictor need not directly conflict with all of the conflicts store=
d
in the conflictor=2E This cannot be so, since e=2Eg=2E a prim can conflict=
with a
conflictor simply because it conflicts with one of the conflicts stored in
the conflictor=2E The side-conditions in the commuteNoConflict cases make =
that
pretty clear=2E
] =
[move v3 helper functions idsFL and idsRL to harness
Ben Franksen <ben=2Efranksen@online=2Ede>**20190710171914
Ignore-this: adb91e53426a7602e0422b360e678a5ca64279ed7125bde9275c247ad1a7a=
4e0334f50bf0cb10a42
] =
[v3: remove debug stuff and other minor cleanups
Ben Franksen <ben=2Efranksen@online=2Ede>**20190710211129
Ignore-this: a8cf0462f87cb0ec43d7a1766554e810d618f6a347784c650a923906d26de=
3b93f3fa66c9ff4e85a
] =
[fix the function used internally in v3 to merge FLs
Ben Franksen <ben=2Efranksen@online=2Ede>**20190710182302
Ignore-this: a961e389d32076bb743fac0c9679e36245ba2320786178eceb40540fef368=
0583c3fbbe2b1316457
=
It is used to merge non-conflicting FLs into a single alternative for
conflict resolution=2E The bug was that we forgot to call findCommonFL and
thus mergeNoConflicts could fail=2E
] =
[make PrimPatchId opaque and check invariant when constructing it
Ben Franksen <ben=2Efranksen@online=2Ede>**20190708161010
Ignore-this: c4fe732deebf074a10265e3d85736bc736fe44e158615bc459d81f08614a5=
c7709e7372e529bbd72
] =
[document and add property for PrimPatchId invariant
Ben Franksen <ben=2Efranksen@online=2Ede>**20190615092033
Ignore-this: 6e00fdb919775f7ddaec3d98bd0c30a2db2419a5348dbc468a00f28c648c7=
9026e549d63c464eef5
] =
[improved test case generator for RepoPatches
Ben Franksen <ben=2Efranksen@online=2Ede>**20190624063022
Ignore-this: f238d840b780add48ccd6fb6e7e02221dbf48096ea8e92885ce3dc9bebfd5=
3b7b0bfd8e0dbec673e
=
We previously generated RepoPatches by merging prims from a Tree=2E While =
this
generates conflictors, it never generates sequences where a patch depends =
on
a conflictor=2E The new generator (which can only be used for patch types =
that
have a Merge instance i=2Ee=2E not prims) directly generates an RL of patc=
hes,
making sure we cover all possible cases=2E
] =
[harness: make sure once and for all that generated Trees have enough patch=
es
Ben Franksen <ben=2Efranksen@online=2Ede>**20190707081626
Ignore-this: f74b5c224e055fc6289096ae2b1e44ce422b50024f6c63adf005988be8564=
31befc67cef3707b1f1
] =
[harness: remove a dirty hack from patch tree generators
Ben Franksen <ben=2Efranksen@online=2Ede>**20190621134136
Ignore-this: 61e9017bd189f4936c59ab8442f7eb827893b1351d9ff5a3e8ac3877ae012=
d02e3a83383e1b65da1
=
This re-adds a slightly modified version of sizeTree which we use to
calculate the number of pairs in a flattened Tree=2E
] =
[harness: move nontrivialX conditions to D=2ET=2EP=2EA=2EGeneric and remove=
dead code
Ben Franksen <ben=2Efranksen@online=2Ede>**20190621194726
Ignore-this: 425ad9283a3e67720a165a6e6255359dce6daabb54a460ff3f2f033493ac1=
776e7bdc7a4e10f5987
] =
[harness: remove unused sizeTree =
Ben Franksen <ben=2Efranksen@online=2Ede>**20190707114205
Ignore-this: e43847945cec7c3fad49895260208dcabdc5babf1fffc3ce3d289ea377086=
b6bb0c64e48a9786f84
] =
[harness: remove some out-commented code from D=2ET=2EP=2EA=2EGeneric
Ben Franksen <ben=2Efranksen@online=2Ede>**20190621133552
Ignore-this: 4ef0c24e4142c4eb0fa4b83487e592bce0b81f75a6f30351048e83e4c4e0f=
4bd5b4b71a6c32b0dd3
] =
[simplify instances Eq2 for RebaseName and RebaseFixup
Ben Franksen <ben=2Efranksen@online=2Ede>**20190630181837
Ignore-this: 1274aa4ac8e5aca8feaa0892cc35ea39aa68c88faa9fecdd7e8bd43112456=
1a4ddcbe11c863764d6
] =
[break an overlong line in D=2ER=2EMerge
Ben Franksen <ben=2Efranksen@online=2Ede>**20190628082123
Ignore-this: b5bfabc35e7b2a0ebaf982323c74dc181fd515c8b544f1a6bc473fa04a7f6=
90d80c0beaf6a72b748
] =
[harness: remove unused propFail
Ben Franksen <ben=2Efranksen@online=2Ede>**20190621133040
Ignore-this: 5a1497663b926b6f1c7b3a2881e480417b4c52d6a5a81f08438619d9d5510=
b2a919200c9320c0762
=
While a comment said this is "handy for debugging arbitrary code" I could
not find an any further explanation or an example=2E I guess it can be
re-added easily if needed=2E
] =
[fix a bug in darcs1->darcs-2 conversion
Ben Franksen <ben=2Efranksen@online=2Ede>**20190226222910
Ignore-this: f65ad0aced1aa6d473b8d59ebc5605daf931c569537214090f541186a967f=
8bf6b201a89139429b6
=
The test data for threewayanddep threewayandmultideps were quite obviously
wrong! The darcs-2 Conflictors are complete bogus, referring to patches th=
at
don't appear in the repo=2E This is caused by erroneous calls to
sortCoalesceFL in the RepoPatchV1 implementation in unravel and in effect=
=2E
The way these functions are normally used (effect when we apply a patch an=
d
unravel to generate conflict markup) is quite tolerant wrt coalescing=2E
However, unravel is also used to convert darcs-1 Mergers to darcs-2
Conflictors, and here the result is catastrophic=2E Instead of sortCoalesc=
eFL
we must merely cancel inverses, just like we do in the darcs-2 and darcs-3
theory when we construct contexted patches (aka Nons)=2E
] =
[resolve issue2626: treat applyToWorking more uniformly
Ben Franksen <ben=2Efranksen@online=2Ede>**20190617063258
Ignore-this: a4a3d604838c74302395a77c6e08a66a0d0383d78fac44db36af32be72deb=
5129ef026cece930b47
=
This factors catching IO errors into applyToWorking with a generic error
message that should fit all use cases=2E In case of the 'convert darcs-2'
command, the extra clarification that suggests to use --no-workingdir has
been removed as I find it misleading and cannot see how that could actuall=
y
help: we have created the whole working tree ourselves, so if applying the
patches fails something really weird (like another process interfering wit=
h
the working tree) must be going on=2E
=
It also adds a number of withSignalsBlocked to wrap the calls to
applyToWorking where they were missing=2E Where possible, the scope of act=
ions
under withSignalsBlocked is extended to include finalization and/or updati=
ng
the pending patch=2E This has previously been the case for some commands b=
ut
not all of them=2E
] =
[resolve issue2625: catch only IO exceptions from applyToWorking
Ben Franksen <ben=2Efranksen@online=2Ede>**20190616112414
Ignore-this: 4257807bb86e85058a430f2bb7de25efd96e76dbcb110a8a686e0e85df7d9=
7f1ab1878e76119400
] =
[rename module Darcs=2EPatch=2EParse to Darcs=2EUtil=2EParser
Ben Franksen <ben=2Efranksen@online=2Ede>**20190217202539
Ignore-this: 2cd7b62ee5cf6015e9f648cc1ddcf120dd7a9f06b7a6934fa28b7c81f7447=
f54c6a1b34797a5115
=
There is nothing specific to patches in this module, in fact we use it for
inventories as well=2E
] =
[add a comment explaining the commuting during revert
Ganesh Sittampalam <ganesh@earth=2Eli>**20190614122900
Ignore-this: e10f994c016df3ea002e24e30368e992
=
I also renamed the variables to make things clearer
=
] =
[harness: more detailed fail output for some properties
Ben Franksen <ben=2Efranksen@online=2Ede>**20190226093418
Ignore-this: 11a41e9f3c7e5d599ade6794d32422f1995a330891726e740340fd5ccca99=
3a91eafe3b3e7ec3100
] =
[move v3 repo properties to harness
Ben Franksen <ben=2Efranksen@online=2Ede>**20190225091504
Ignore-this: 8bde91c045669b4d785d9a658b9b52b898c130ae5106e7358d067f685323a=
3c19d84a228b81730ac
=
This is so we can use Darcs=2ETest=2EUtil=2ETestResult and give better out=
put when
testing the property fails=2E
] =
[remove unused method isConflicted from class Conflict
Ben Franksen <ben=2Efranksen@online=2Ede>**20190301185825
Ignore-this: b9b542bbe788194b8c6fdcfb3d7c70edebf34b76227b314df1f3d1fa6bbbf=
f962575bbdf5835fb21
=
Besides, we already have it as (isNothing =2E toPrim)=2E
] =
[remove the obsolete PatchInspect superclass of Conflict
Ben Franksen <ben=2Efranksen@online=2Ede>**20190227230137
Ignore-this: 735d0cdf081ee726b4799d2fc16f4011fdbc899b0c63f6a8b716ff43e1228=
c421d393a99e3b4cc3
] =
[harness: remove qc_V2P1 and qc_V3P1
Ben Franksen <ben=2Efranksen@online=2Ede>**20190225101544
Ignore-this: 4c6e5161e8255083ce81f9be1596d42c04630df8058f0ade412f44327cf8d=
94ec11610b3e67a3035
=
The properties listed therein do not in any way depend on the prim patch
being V1=2E So I generalized the signatures and moved the tests to qc_V2 a=
nd
qc_V3, respectively=2E
] =
[declare instances of IdEq2 for Named, NamedPrim, and PatchInfoAnd
Ben Franksen <ben=2Efranksen@online=2Ede>**20190224080814
Ignore-this: 89d31c807008dd022dbadff8c514b7d7971cff6658751f9383618f3a8ffdc=
f2c4621d4b505b7d06
] =
[fold partialPermutivity into permutivity property
Ben Franksen <ben=2Efranksen@online=2Ede>**20190223094647
Ignore-this: 567469e46368f0da6e89adaad2f3e33cab5f012b2827b4e9b56e3c402bbab=
ccec1e24cecd056d84f
] =
[replace our own patch parser with attoparsec
Ben Franksen <ben=2Efranksen@online=2Ede>**20190217111256
Ignore-this: c64d383cab9f491eefed0fd899779aeee209a196fb8081454332f595b4d02=
cc1b0d0539eba3ec02f
=
We already depend on attoparsec for convert import and its functionality a=
nd
implementation is quite similar to our self-written parser monad=2E I have
checked that this does not impact performance negatively=2E
] =
[optimize parsing of PrimPatchId
Ben Franksen <ben=2Efranksen@online=2Ede>**20190216113744
Ignore-this: 2cbf157b49fcca77248c240cdca76a9bf65bc7c7210299b5625e492a1b250=
ede01bb488f2f0fd41c
=
Profiling showed that a lot of time was spent inside b16Dec when reading v=
3
patches=2E We now read the SHA1 directly off the ByteString which is much
faster than going via b16Dec and binary decoding=2E Also fail properly in =
the
parse monad if the hash is malformed rather than calling error=2E
] =
[add more detailed comments for some cases of findConflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20190215161223
Ignore-this: f4e9e6b12267be5026752bdeb437b8986df3e2a0cc505e8abb32277a0bb3d=
3520a22a3b635d97d22
] =
[fix prop_conflictsCommutePastConflictor
Ben Franksen <ben=2Efranksen@online=2Ede>**20190215155817
Ignore-this: 66c198d17461ac90450d37a4b47cf912ee5a52f16277aa5b86a76cd62bc90=
a9fac759b55fb203a68
=
The property was almost correct but not quite=2E Indeed, patches we confli=
ct
with may not individually commute past the conflictor because of
dependencies between these patches=2E However we can always commute them t=
o a
contiguous segment right before the conflictor, and then commute them past
the conflictor as a whole=2E
] =
[add a number of INLINE or INLINABLE pragmas
Ben Franksen <ben=2Efranksen@online=2Ede>**20190215111230
Ignore-this: 36cde62676771b68e151121c1028c0dea46d6b4e4b3ab9f06a49e3f1f10c0=
6e48b48d8d9dfb6cf50
] =
[implement resolveConflicts for RepoPatchV3
Ben Franksen <ben=2Efranksen@online=2Ede>**20190213191419
Ignore-this: 5930378d244113a2c1ec5a25ebea540fddcfaa0991403d0f46ee0e3ce3b7b=
7a0818c1a26a28dad52
] =
[change the type of resolveConflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20190213172409
Ignore-this: 77cdb5896438291f91e9a4b64f3c165beffb1b042d5ff8af49e729a20be1e=
80228d8cc0ed0a72288
=
It now gets two RLs of patches as input and produces a simple (not nested)
list of resolutions=2E The change in the input type(s) has been done becau=
se
otherwise a RepoPatchV3 cannot correctly implement resolveConflicts, which
requires that we know the transitive set of conflicting patches for each
conflict=2E But a V3 conflictor contains only the patches that directly
conflict=2E The separation into two input RLs is so that we can still reso=
lve
only the conflicts inside a (trailing) segment of all patches in a repo,
which is how we call it when merging patches=2E
=
There are no longer instances of class Conflict for RLs and FLs=2E Instead=
, we
offer the stand-alone function combineConflicts and use that in the
implementation of resolveConflicts for RepoPatchV1/2=2E
=
The change in the result type is just a cleanup: instead of adding the
mangled resolutions as a first element and then taking the head (in
standardResolution) we now replace the inner list with the mangled version=
=2E
=
Passing the full context to resolveConflicts requires a number changes
downstream=2E This is not strictly needed for V1/V2 which ignore the conte=
xt,
so we could pass undefined, but we need to make this change for V3 anyway=
=2E
Instead of adding yet another parameter to all functions involved, we now
pass a (Fork common us them) which cleans up type signatures (and
incidentally some of the code, too)=2E
] =
[show the PrimPatchId only ForStorage, not ForDisplay
Ben Franksen <ben=2Efranksen@online=2Ede>**20190212171739
Ignore-this: 14e9d992008886472c8074eb51478b87ddc92a0f9166796697678a7f7800f=
77e3b6f33800b4e8a90
=
The PrimPatchId is not useful to the user and clutters up the output when
--verbose is in effect=2E It also allows more test scripts to pass without
having to adapt them=2E
] =
[bugfix in instance ShowContextPatch for NamedPrim
Ben Franksen <ben=2Efranksen@online=2Ede>**20190210204803
Ignore-this: 68a4bfee97592c22cbe1db6e2c9f55619ec5202e4b80a8a6eed7368c579a7=
7c7234009fb49e62f6f
] =
[add Darcs=2EUtil=2EGraph
Ben Franksen <ben=2Efranksen@online=2Ede>**20190209161000
Ignore-this: 124741eb525d8358ac597505bafa83045427a876de6edf9aa1b13f1d02499=
265e15fe3ac614d7966
=
This contains an efficient algorithm to determine maximal independent sets
of an undirected graph=2E
] =
[separate class Summary out from class Conflict
Ben Franksen <ben=2Efranksen@online=2Ede>**20190209122716
Ignore-this: 72faff5442a74f6d7e36d07c5d32a8205e520713009a01d7728a297d17c7a=
dd1387def4c422d6c5a
=
This prepares a change in the type and meaning of resolveConflicts but mak=
es
sense independently=2E The method conflictedEffect is used only to generat=
e a
summary for potentially conflicted patches and thus has been moved to the
new class Summary=2E The class Conflict gets a new method isConflicted whi=
ch
just returns whether a patch is conflicted or not=2E
Incidentally this gets rid of a number of unneeded instances for Conflict
with nonsense/dummy implementations for resolveConflicts (such as for Name=
d,
PatchInfoAnd, RebaseChange, and RebaseSelect)=2E
] =
[fix instance MightBeEmptyHunk for NamedPrim
Ben Franksen <ben=2Efranksen@online=2Ede>**20190209135159
Ignore-this: b1086cabaaab6213c883e46b2f628c627865a904b94b0ecea32b8c4b82cbd=
00da8bd4ff8ae93e3c6
=
Property effectPreserving fails for Prim=2EV1 empty hunks, and so it does =
for
its NamedPrim wrapper=2E
] =
[fix in the QC generator for prim patch IDs
Ben Franksen <ben=2Efranksen@online=2Ede>**20190209134332
Ignore-this: 91ebf416d68a3e32c88a4b57f2b215d2a714c83ba9d52f7044ba9cf6c10b7=
95f0cb05a7725481dbb
] =
[restore alphabetical order of exposed-modules in darcs=2Ecabal
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208164649
Ignore-this: 8e8b4a08b048a798154b8545ec1eda37a4078baae2163b901cc2f64abfdfa=
10f7d0aad145cbf361f
] =
[move Darcs=2EPatch=2EV3=2EPrim to Darcs=2EPatch=2EPrim=2ENamed
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208164649
Ignore-this: 11c6b305355e9d6b75e3f02ca85dc3246d220886c1d5d133ba1dcea8d68d9=
4fc76ade6e8e8924d74
=
This is actually a fully generic wrapper for any PrimPatch type and
technically not tied to V3=2E
] =
[add prim patch identifier when constructing Named patches
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208164649
Ignore-this: f57ffc7d3a83e9779566083826ee3b2b46048f78267100ea9a54e9bd94cb5=
02ebfdc712e48f2f2f3
=
This re-adds method fromPrim to class FromPrim, this time with additional
parameters to construct the identifier=2E This is then used in function
infopatch instead of fromAnonymousPrim=2E
] =
[renamed fromPrim to fromAnonymousPrim
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208164649
Ignore-this: c48e828a89e8afd62066c77998c5cd18584060e279f92823d7496cd823316=
426a7649606fc03e82a
] =
[add V3 stuff to the test suite (quickcheck tests only)
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208164538
Ignore-this: 4a6082f0fdd9a47b753fa9f020bc87cad4d7c8fed450ac497660aec14a7fc=
8ba59a9071d1c4e951c
] =
[add RepoPatchV3 aka camp conflictors
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208164513
Ignore-this: feeb4c3e9c99f20f77cb5980bad455e454715b484b2b5185195a2455e7e14=
abb6563a5e08c2faccc
] =
[add some functions we need for V3 to Darcs=2EPatch=2EIdent
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208155041
Ignore-this: dbe9d108136fda53b93c507df62c94f3ac15a8fc1b614c23358e0aa15b444=
b1675f863ec4fe190b1
] =
[treat 'failed to commute common patches' as a bug
Ben Franksen <ben=2Efranksen@online=2Ede>**20190612153925
Ignore-this: 6294bf4989e8665e278230a8166a6892203a2f5ed5c0781bcb15165ddd7b7=
f2e7e8ba5e2895b8383
=
This partially rolls back
patch 7448ac2618ae158dbe576e45f487d24e9c71170c
* add new Exception types CommuteCommonPatches and PatchNotAvailable
] =
[split up Darcs=2EUI=2ECommands=2EConvert
Ben Franksen <ben=2Efranksen@online=2Ede>**20190226182702
Ignore-this: 664d576d3951885f994bfe7fd559a53ad0359e202107415755bca007569b0=
1ff3afab182a82745d8
=
The implementations of these commands are long and complicated and they
share almost no code=2E And we need to add yet another command for convers=
ion
to darcs-3=2E=2E=2E
] =
[harness: slightly improve docs for generic properties
Ben Franksen <ben=2Efranksen@online=2Ede>**20190226091049
Ignore-this: e10a9008733ea6205413b55617ed0d9b3fba9f7bdb1f5d7bbf5553c9ccaa6=
10e7699b4ed4f76b6ca
] =
[harness: print failures with color =
Ben Franksen <ben=2Efranksen@online=2Ede>**20190225091643
Ignore-this: b06c0f191ba8b31180f8228c9680c3c455287955bfedde9935ef4ff29f86b=
7c7fed5d3a15f787521
] =
[fix in tests/convert-darcs2=2Esh: add missing "cd =2E=2E"
Ben Franksen <ben=2Efranksen@online=2Ede>**20190226214009
Ignore-this: 7593682e01c1f22e9b12e93aa6bdc9d93ec81445f938577bdb84a9ae22f3a=
34150f98169d245edf8
] =
[make it clear that coercing Repository is "unsafe"
Ganesh Sittampalam <ganesh@earth=2Eli>**20181118220143
Ignore-this: a6c3812e365d19cd17377fe146dda216
=
This may be a little pedantic, especially as we don't claim that
mkRepo is unsafe, but it's consistent with the API for patches=2E
] =
[use mergeNoConflicts in the definition of standardResolution
Ben Franksen <ben=2Efranksen@online=2Ede>**20180916104610
Ignore-this: 146e0e181392dbee9f1286bef5e4c1035b0fd68208e78e33d75b5aff63d6b=
32168cbc6f446779b91
] =
[replace use of fromAnonymousPrim with call to constructor
Ben Franksen <ben=2Efranksen@online=2Ede>**20190208164954
Ignore-this: 43e342cde5dc6e4985b875276b0b7d984e7c3163434b049b37e1098456dd7=
5e0363072588ad9416
=
This further minimizes calls to fromAnonymousPrim which is good because wi=
th
V3 this is now an unsafe method=2E
] =
[better diagnostics when property mergeEitherWay fails
Ben Franksen <ben=2Efranksen@online=2Ede>**20190205105245
Ignore-this: 2cc1b0a1357bd305a63ead1fe6e1120637ce8969fab1b01705db2b28e2070=
dbe26bff863f68dfa16
] =
[rollback of rename conflictedEffect to isConflicted
Ben Franksen <ben=2Efranksen@online=2Ede>**20190209115302
Ignore-this: 846fbce4cea91f41337b551ff6a650a7f9ff58159c5b7462fcde2153ce01b=
e01c7cf0568d5eb315b
=
Contrary to what I stated there, conflictedEffect does have a lot to do wi=
th
the effect of a patch=2E It is just in the wrong class which I am going to=
fix
in another patch=2E
] =
[resolve issue2618: option --ask-deps adds too many dependencies
Ben Franksen <ben=2Efranksen@online=2Ede>**20190124183655
Ignore-this: 99b3f4b4f6e72a80773321890a3ae6b08bf2b2121e5590db51ae4aec503ed=
d253f84818c5f2e0ac4
=
The trick is to filter out any patches in the result from runSelection tha=
t
depend on later ones=2E While this may also filter out explicitly selected
patches, these should rightfully not have been offered in the first place=
=2E
I took the freedom to clean up and simplify the code for askAboutDepends=
=2E
This concerns mainly the initial filtering of patches that are depended on
by what we record, which is now reduced to a plain commuteWhatWeCanRL=2E
] =
[accept issue2618: option --ask-deps adds too many dependencies
Ben Franksen <ben=2Efranksen@online=2Ede>**20190124183618
Ignore-this: 3c530e6336303b14ab82382d755cd50f37aa7115891e465a6dbf3ea438939=
8b1e7ecc01d0f46a935
] =
[annotate all uses of anonymous with comments
Ben Franksen <ben=2Efranksen@online=2Ede>**20190123184250
Ignore-this: e36396a975c47090fbd77903cb3948ded7ba576e723a3963f5e48c505d7b1=
729d70940a846a0850a
=
Whenever we call anonymous to construct a Named patch we must now check
that we don't accidentally store patches that result from merging them
with normal patches=2E
] =
[add class IdEq2 to Darcs=2EPatch=2EIdent
Ben Franksen <ben=2Efranksen@online=2Ede>**20190124135342
Ignore-this: c5466acfb13224c405ebfe055b186d2a57d0d9d53dbf6044facba677efe0d=
ba803c865e3469e8cde
=
This allows a faster equality test for FLs of patches with identity=2E
] =
[remove class PrimPatchCommon
Ben Franksen <ben=2Efranksen@online=2Ede>**20190123145855
Ignore-this: a928a57c0712f3e27971cc2df9bb30763581f11f8e18bf28d9bddd441a6b4=
ec2d67b2b60a6d6de78
] =
[avoid direct imports of Darcs=2EPatch=2EFromPrim from outside of Darcs=2EP=
atch
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122194221
Ignore-this: f3526d3539faa6b8a0f3c7f547fa95d4a2d1acaac062b6e5465e5cc4f2c7b=
63b3ed356eb5cf026a1
=
The only exception is now the implementation of rebase inject which needs
low-level access to fromPrim=2E
] =
[remove fromPrim from Darcs=2EPatch
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122193314
Ignore-this: 5466d3c0d875be04d4d987230016b2ed5ce623aef2d4cf31113d73c0244c3=
f751c348fc38236487e
=
This is now no longer an official part of the Patch API=2E
] =
[move classes PrimPatchBase, FromPrim, and ToFromPrim to their own module
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122192439
Ignore-this: 7a05d15ffab8643ee34adffdca910beb4628c478cc98eb7fd114244a00b44=
8d9a46d63f459622e8e
=
These classes are not part of the Prim patch API but the RepoPatch API=2E
] =
[move instance FromPrim (FL p) to Darcs=2ETest=2EPatch=2EExamples=2ESet1
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122184024
Ignore-this: 46af7bff9fa0123cbf9341529ba5b69a5e44a1a589d1ea87b5a6f8829d701=
d7f97651716b0ddcbb2
=
This is the only place where the instance is used=2E
] =
[remove instances for FromPrim and PrimPatchBase for prim types
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122183012
Ignore-this: 756b3fd6b00bcd2a2d4af647a9dda4b645023bfd24f136fb8d7530afcc687=
ae5d3f96622fb2b7ece
] =
[eliminate use of fromPrim in convertDarcs2
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122175720
Ignore-this: f49d305cb77f4260a6bafab2fd9a96b297b441e1c5e9aee711d0a44eee52b=
3ae3f4b010e55179088
=
The code now uses the data constructor V2=2ENormal instead=2E
] =
[eliminate an unneeded use of fromPrim
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122173108
Ignore-this: 3b97bef8e57f2ae1fb571f6ec5a5b817e4ff097d7fc2698ef7e258d54dd9d=
d7d4009f783244b51af
] =
[refactor: eliminate class FromPrims
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122172158
Ignore-this: 54d76dec03513588d7bf8b59c79aa24c6af77c5b4d106b2fbd33e3de2e9d0=
6d6ed7aa01c4f325fb8
=
Again, preparation for adding identities to prim patches=2E The method
fromPrims was used mainly to construct Named patches via infopatch or
anonymous from Darcs=2EPatch=2ENamed=2E These functions now take an FL of =
prim
patches as input=2E
] =
[inline function Darcs=2EPatch=2ENamed=2Enamepatch
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122132111
Ignore-this: 4a9fbb4c69164a54029c50bcb7ff3b369728de13989296b4132d52b92b4fa=
df038a7f1da62d79a6c
=
This is in preparation of adding identifiers to prims when constructing
named patches=2E
] =
[simplify "Ignoring out-of-order tag" warning for darcs convert import
Ben Franksen <ben=2Efranksen@online=2Ede>**20190124110533
Ignore-this: ffba102334ae16c01c5d8cae9c3355913c5ae50c89675186b0926d96a43df=
767d162fc8ffa16d378
] =
[add new Exception types CommuteCommonPatches and PatchNotAvailable
Ben Franksen <ben=2Efranksen@online=2Ede>**20181214153646
Ignore-this: ea1cdebcb8df41910e606c7eb0523b6c7b2eaaef0de12e297f2568498f932=
efe3c50ef77398bf82e
=
We now throw these special exceptions instead of calling error=2E This is
because neither is (necessarily) a bug in Darcs=2E Instead these exception=
s
can be thrown under normal conditions and indeed there are tests that
provoke these failures=2E
] =
[replace errorDoc, assertDoc, bug, and impossible with direct error calls
Ben Franksen <ben=2Efranksen@online=2Ede>**20181214153646
Ignore-this: bc37ba5af9afd01725140e6f008839811b0e17058f0fe7d531998017d0c0d=
a6d5393430840765653
=
All of these functions indicate the same thing: if they are evaluated then
this is a bug in Darcs=2E In case such an error happens we want to know th=
e
file and line number=2E If we use any of these functions, then the locatio=
n we
get from ghc is only an unhelpful src/Darcs/Prelude=2Ehs or
src/Darcs/Util/Printer=2Ehs=2E That is, unless the callstack actually cont=
ains
useful information, which apparently requires profiling to be enabled=2E S=
o
this is useless to us in practice because who uses a special
profiling-enabled Darcs in their daily work?
] =
[replace a few calls to 'bug' with 'fail'
Ben Franksen <ben=2Efranksen@online=2Ede>**20181214153421
Ignore-this: 8f0741d3fcdfbbbae4bb220a1f6bcf2f7d0391f13ff01ed82798321757599=
523c52c7f5079c85be2
=
These aren't bugs in Darcs at all, instead they are normal failures=2E
] =
[resolve issue2617: convert import crashes with out-of-order tags
Ben Franksen <ben=2Efranksen@online=2Ede>**20190122161346
Ignore-this: f3789fbca9eea248c160b99717d411037e9597a531c2a053a2c77cd7eb6bb=
a9d1754c97eb9ecfc9b
] =
[support QuickCheck 2=2E12
Ganesh Sittampalam <ganesh@earth=2Eli>**20190116061531
Ignore-this: e907466ec9d44ac9fc309e40fa82bcfc
] =
[support zip-archive 0=2E4
Ganesh Sittampalam <ganesh@earth=2Eli>**20190116052802
Ignore-this: 53bd6a4c63f1dc0c98c2dfa4fe6f578d
] =
[RepoModel tests: replace Either with an explicit failure type
Ganesh Sittampalam <ganesh@earth=2Eli>**20190115065956
Ignore-this: 200c9c8fd864a98063dd76a510c9ab0c
=
This means we can have a non-orphan MonadFail instance=2E
=
Immediately before this change fail on this type would
have just called error, but the code dates from before
the explicit fail definition was removed from Either in 2010,
so this probably restores the original intention=2E
=
(see https://ghc=2Ehaskell=2Eorg/trac/ghc/ticket/4159)
=
] =
[treat path to unrevert bundle like all other repo paths
Ben Franksen <ben=2Efranksen@online=2Ede>**20181204184737
Ignore-this: a67547eb79315034ea92fc3b47b1bb2b3484af0a4e5aa07a53b28dd37359a=
26f089058ba0b3fcdee
=
This means that we treat it as relative to the repo base directory instead
of having it depend on the repoLocation of our Repository=2E Also factors
unrevertPath to Darcs=2ERepository=2EPaths=2E
] =
[minimize context inside unrevert patch at the head of the unrevert bundle
Ben Franksen <ben=2Efranksen@online=2Ede>**20181116085505
Ignore-this: a910c970ca9cf54ba7bbd9c8b639268521630e1d09c9949750b4d647fe27a=
854ebabe2919c144879
=
This does not minimize the context consisting of named patches in the bund=
le
itself=2E Instead, only the prim patches that go inside the anonymous patc=
h at
the head of the unrevert bundle are affected=2E
] =
[remove duplicate definition of catchall in Darcs=2EUI=2EExternal
Ben Franksen <ben=2Efranksen@online=2Ede>**20181115211847
Ignore-this: ea0f1fedcdcd8592e3d18925310df3953bd76f123aef0cfcd4197d13de339=
e32d68ae1123daba9e5
=
Instead use the one from Darcs=2EUtil=2EException=2E
] =
[revert command: break overlong lines (layout only)
Ben Franksen <ben=2Efranksen@online=2Ede>**20181115195735
Ignore-this: 831c4d382396cc6c78c623b07ae27d9b1d6099f9ea431a2f4865d9a2fb6aa=
5caeef596e6549aeeb6
] =
[D=2ER=2EMerge: use displayPath for path display
Ben Franksen <ben=2Efranksen@online=2Ede>**20181114210502
Ignore-this: 1579729958cfa3cde5964db125e126dbd870f95248131fbf4d0f32b6a15fd=
036905eb9f899606340
] =
[move removeFromTentativeInventory closer to its single call site
Ben Franksen <ben=2Efranksen@online=2Ede>**20181113101957
Ignore-this: 33863d10e41a0a82de494a7c9d421bec57c1c0e61c6493823200328e715d5=
78ab5649ea2384206ac
] =
[removed unneeded pseudo-instances for class Effect
Ben Franksen <ben=2Efranksen@online=2Ede>**20181018102651
Ignore-this: ff7c46758f59624261bd27d2c155fee465cb12bc2c103f1b1eeb455465f8f=
77fa1714c12f930209b
] =
[fully respect the useIndex option
Ben Franksen <ben=2Efranksen@online=2Ede>**20181203182954
Ignore-this: 2ffeb71ab73962267e4db6092fb7e29081faab86419e478f6e26d4685cc13=
3eb8de75f8a8c7f02b6
=
This hopefully eliminates any remaining unchecked uses of the index=2E
Darcs=2ERepository=2EState now contains a CPP macro TEST_INDEX to control
whether some testing code is included that accesses the index /and/ does a
readPlainTree with an appropriate filter and then checks that the resultin=
g
trees are equal=2E We also pass the repoLocation explicitly to readPlainTr=
ee
now (if available), because it turned out that some uses of the functions =
in
D=2ER=2EState are made with a CWD that is not equal to the repo base dir=
=2E
The implementation of readUnrecorded is now in terms of
readUnrecordedFiltered instead of repeating ourselves=2E
] =
[rollback of "resolve issue1959"
Ben Franksen <ben=2Efranksen@online=2Ede>**20181203181310
Ignore-this: d2a01578d01e78c05b7d39179b4e6118099da55c615c296fb8b87a13813d3=
fad7e978de7c85508d4
=
This change is unsound for several reasons=2E One is that catching permiss=
ion
errors is unreliable as it can depend on the OS what kind of IOError is
thrown=2E Another issue is that catching these errors may hide problems fo=
r
repo-modifying commands like add and remove where we rely on the index bei=
ng
updated or at least being invalidated properly=2E
] =
[fix: insert a valid date when creating anonymous named patch
Ben Franksen <ben=2Efranksen@online=2Ede>**20181116202605
Ignore-this: 69775e49e45c1591b6858c4580e882795524ba8a442d1be6b4874062444f9=
6e285a828f972ac0f3c
=
Otherwise we get an exception when we try to e=2Eg=2E display the patch=2E
] =
[resolve issue2603: warn and mark conflicts when cloning
Ben Franksen <ben=2Efranksen@online=2Ede>**20181114210030
Ignore-this: 4d617184171486dfdb64dcb87f81057896d0fd0f2db1d9f189ab8eb30fb7e=
cc494463966f9e69252
] =
[accept issue2603: clone repo with unresolved conflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20181114203228
Ignore-this: b541ac623a22499592261783d33eaf90595ca51e331809e4d371bf8bf87d2=
1ca4d7116290d409b12
] =
[remove duplicate definition of invertCommuter as inverseCommuter
Ben Franksen <ben=2Efranksen@online=2Ede>**20181031160755
Ignore-this: 805b23e32cfafa5b956b34214a043702ce7cd910a30d455489cd5be81ba14=
ef29acf21f94b6c6506
] =
[resolve issue2604: remove --reply and related options
Ben Franksen <ben=2Efranksen@online=2Ede>**20181012230927
Ignore-this: 95ca795c7cb43c7400f23da7256516130bb730069129bc7d83bb43e73c2f5=
eeaca02c19423c9bf4a
=
The options are: ccApply, reply, happyForwarding and were supported by the
apply and push commands=2E This patch removes all conditional compilation =
from
Darcs=2EUtil=2ECompat=2E It also removes the dependency on the random pack=
age when
building for Windows=2E
] =
[disentangle D=2ER=2EState=2EfilteredWorking
Ben Franksen <ben=2Efranksen@online=2Ede>**20181002212643
Ignore-this: 366cca7d58b10eb1437fec6dc11c9e2a79d59d3a7173967b6a40bb41b98b3=
5f554c30c115b231e32
=
Swapping the order of the cases and then trying to pull out applyTreeFilte=
r
relevant made it apparent that
(a) using the index in the IgnoreIndex case can be replaced by passing the
pending_tree instead, and
(b) applyTreeFilter relevant was missing in the UseIndex+ScanKnown case=2E
] =
[fix in harness: don't suppress output from failed HUnit tests
Ben Franksen <ben=2Efranksen@online=2Ede>**20181011074925
Ignore-this: 23ee906a82e661bf4b3d3bf5255ce95e03c903f3dfd0c28eab57e0c373f00=
c3aa6dead050b95faf7
] =
[print remote execution failure message to stderr
Ben Franksen <ben=2Efranksen@online=2Ede>**20181012213658
Ignore-this: 503c5d9b507d60924df276a19efa4be8897c9038ae83368a484df90e1db47=
470cc4f7838b8cd3ca8
] =
[D=2EP=2EMatch: layout changes to avoid overlong lines
Ben Franksen <ben=2Efranksen@online=2Ede>**20180923174752
Ignore-this: 607cfd8e704e83e5d59f6e0f221f8f97
] =
[patch index: replace fn2fp with displayPath
Ben Franksen <ben=2Efranksen@online=2Ede>**20181014090111
Ignore-this: ba08371018fffd2957a8616c50e91233e75c752557a12a6ad6bb8d56d405d=
4cfdf58da2ff12c5aff
] =
[patch index: clean up import and export lists
Ben Franksen <ben=2Efranksen@online=2Ede>**20181014085600
Ignore-this: 384f78dd7cf592b3a0e918338fa1a8b7a5b6e5e4ece20896cca4756d02812=
eddf132623e2d6f654e
] =
[add progress reporting to patch index
Ben Franksen <ben=2Efranksen@online=2Ede>**20181014083856
Ignore-this: d6caeb553930ada3e7c4ae4f6fa99130bb30478e07b0e0e9df7962465fb3d=
ff31e36c148727d6609
] =
[fix in patch index: use removeFile, not removeDirectoryRecursive to remove=
noPatchIndex
Ben Franksen <ben=2Efranksen@online=2Ede>**20181014082907
Ignore-this: e7aae98873b4c7a3f83536b2228cedc8de9ed534413f2ea7caa4e303d165b=
d884c7cf1d9c617ec8
] =
[rename FileName to AnchoredPath and remove the type synonym
Ben Franksen <ben=2Efranksen@online=2Ede>**20181011212536
Ignore-this: 884cf842b0855404bb9300f92aaac123040e122ca3963ce4fef20880ff80a=
c8789379834ed1d2561
] =
[use AnchoredPath instead of FileName for internal path representation
Ben Franksen <ben=2Efranksen@online=2Ede>**20181011211834
Ignore-this: 4a62454e764a04280bc2fe153fce932dc5e5f555e8629be860c5e26116743=
4e5e2ecf3564f551d8
=
This is a large patch that touches many files=2E I have tried hard to make
reviewing it as easy as possible by avoiding changes that aren't necessary
to achieve the goal=2E For instance, in this patch, FileName is still used=
but
is a synonym for AnchoredPath=2E I have resisted the temptation to include
cleanup changes, except where it was necessary for me to make sense of
existing code=2E
=
AnchoredPath is now used throughout, from the UI down to the patches
themselves, for all paths that potentially reference user content in a
repository=2E This means paths under _darcs are /not/ included, and neithe=
r
are paths /to/ a repository or a cache or other files not under darcs
control=2E
=
Arguments from the command line are sanitized and converted to AnchoredPat=
h
early on=2E This is now concentrated in two routines: pathsFromArgs, and
pathSetFromArgs, see their documentation for details=2E We convert to File=
Path
only for IO operations or for display to the user=2E
=
Parsing of prim V1 patches is a bit stricter now: it fails if paths are no=
t
explicitly relative i=2Ee=2E start with "=2E/"=2E The standard constructor=
for the
Name type (makeName) now checks that the invariants aren't violated, that
is, a Name is never empty, "=2E", or "=2E=2E"=2E Unfortunately, the index =
code still
needs to use unsafeMakeName because it violates these invariants, at least
temporarily=2E
] =
[delete commented out code
Ganesh Sittampalam <ganesh@earth=2Eli>**20181017054933
Ignore-this: 141d9e1511190a3bc6dd0d60c263a356
] =
[move mangleUnravelled to new class PrimMangleUnravelled
Ben Franksen <ben=2Efranksen@online=2Ede>**20181003184913
Ignore-this: 1ba0a4b9437bc75f58db069ed33277c4067516fe61fa9da92d2706fe6232e=
cd3b8fcb2029724071
=
This refactor serves two purposes: First, we isolate yet another bunch of
code that heavily depends on Prim=2EV1, similar to the recent introduction=
of
PrimSift=2E Second, while this is support code for generating the conflict
resolution markup, it is not related to conflictors or conflicts per se; i=
n
fact, it works on and uses only features of prim patches=2E
] =
[remove excessive debug output in D=2ER=2EHashedIO
Ben Franksen <ben=2Efranksen@online=2Ede>**20180930172235
Ignore-this: e874542daf908b7bbbd67aa6fa1636b5f42799d1a6f2c01f187b114955322=
82d1de5b1da39eceffd
] =
[eliminate hard-coded repo paths from the UI layer
Ben Franksen <ben=2Efranksen@online=2Ede>**20181003185748
Ignore-this: f90032e9a8e52b7f3fc55295befa08f03ac3fede42a495a2b0c91feda1b96=
3431ae757f6c2f48010
=
There is one exception in darcs convert where we create a "marks" file
inside _darcs but I guess this is an ad-hoc addition=2E
=
Note that this is the first time this operation of concentrating repo path=
s
to a single module actually pays off: in the convert implementation we use=
d
a wrong file name _darcs/tentative_hashed_pristine (the correct name is
_darcs/pristine=2Etentative)=2E So this also fixes a bug=2E
] =
[fix in output of log command
Ben Franksen <ben=2Efranksen@online=2Ede>**20181007165339
Ignore-this: 1c8666e31ec6b5103bad9b9864b09faa70849f2e357350e75b11ed7345d91=
2f39f823dc9b643ed80
=
I think the 'not' here got lost during a refactor=2E
] =
[resolve issue1959: catch permission errors when accessing the index
Ben Franksen <ben=2Efranksen@online=2Ede>**20181002230526
Ignore-this: 2477c259bf7e9998c699b56a13dccc2187839f5271be678f85e6f2c86bc10=
2e313526f4799d14da9
] =
[use cryptonite instead of cryptohash and random
Ben Franksen <ben=2Efranksen@online=2Ede>**20180921142554
Ignore-this: 331cdff4ee3a495fd0c8fbcb2a2563d5
=
This also replaces our own implementation of SHA1=2E
=
It is unfortunate that we have to add the memory package as a dependency
but there is currently no other way to get at the content of a Digest=2E
] =
[factor yet another bunch of repo paths to D=2ER=2EPaths
Ben Franksen <ben=2Efranksen@online=2Ede>**20180922153612
Ignore-this: 4be35b34f99043bb88979727aa0c7a6
] =
[avoid needless String/ByteString conversions when reading format file
Ben Franksen <ben=2Efranksen@online=2Ede>**20180922122839
Ignore-this: d9ebfdc76eda57e29f7dba52b122f0af
] =
[reliably fail if we detect that an old-style rebase is in progress
Ben Franksen <ben=2Efranksen@online=2Ede>**20180920135615
Ignore-this: fc4023a78ddae501af398916c1b4554f
=
The trick is to check if the repo type is tagged with SIsRebase, which mea=
ns
that the repo format has rebase-in-progress, and then count the suspended
patches in the new-style rebase patch=2E If it is zero we can assume that =
we
have an old-style rebase in progress=2E
=
While the check itself is simple, making sure it is called with the right
parameters at the right time is not=2E One problem is that we must make an
exception for the 'rebase upgrade' command=2E This is achieved by adding a=
new
kind of RepoJob (OldRebaseJob) just for this command=2E A further complica=
tion
arises because startRebaseJob is called with an SIsRebase-typed repo
regardless of whether a rebase was in progress initially or not=2E In this
case we cannot decide whether to run the check based on the repo type alon=
e,
but instead have to (re-)test the format stored in repository token=2E
] =
[add command 'rebase upgrade'
Ben Franksen <ben=2Efranksen@online=2Ede>**20180919201151
Ignore-this: 2336365ca25c08b3366c2a05f2a6ac8
=
This required a few additional refactorings mostly in D=2ER=2EHashed=2E We=
lift a
local function to the top level that (lazily) reads the patches from a
single inventory=2E Since this does not return a PatchSet but only an RL o=
f
PatchInfoAnd, we can generalize it to return PatchInfoAndG and so can be
used with WrappedNamed instead of Named=2E The WrappedNamed has been
resurrected and largely cut down to what is needed for this single purpose=
=2E
] =
[use englishNum for correct grammar in rebase status line
Ben Franksen <ben=2Efranksen@online=2Ede>**20180919231029
Ignore-this: cfca8a805b760612c7ddef031445daef
] =
[add PatchInfoAndG which is polymorphic in the named patch type
Ben Franksen <ben=2Efranksen@online=2Ede>**20180919095655
Ignore-this: aa2fdfd81cb236f2db7886dcbc7fb7cc
=
The standard PatchInfoAnd is now a type synonym that fixes the named patch
type as 'Named'=2E Unfortunately this required the addition of Eq2 constra=
ints
in lots of places=2E
=
The goal of this generalization is to be able to convert old-style rebasin=
g
repos, for which we need to read PatchInfoAndG with a simplified version o=
f
the old WrappedNamed as the named patch type=2E
] =
[remove the WrappedNamed layer
Ben Franksen <ben=2Efranksen@online=2Ede>**20180918171323
Ignore-this: 2f29e084bd43127dcda265f3729ee882
] =
[two fixes in clone and convert import commands
Ben Franksen <ben=2Efranksen@online=2Ede>**20180918021046
Ignore-this: 151345be0c286e0ef17c07cb67593fe0
=
The bug was in both cases that finalizeRepositoryChanges was not correctly
paired with revertRepositoryChanges=2E This was exposed by the new way of
storing the rebase patch, which crashes when it tries to rename the
tentative rebase patch back to its final version=2E
] =
[store rebase patch at the repo layer instead of mixing it with normal patc=
hes
Ben Franksen <ben=2Efranksen@online=2Ede>**20180918170040
Ignore-this: b53e98ddc25a3b21a5a30eb552e1f5b0
=
This does not yet do away with the WrappedNamed layer and the
RepoType/PatchType cruft, which will be done in a second and third step=2E
Some tests now fail which is due to bugs which are only weakly related to
the change made here, so will be fixed in a follow-up patch=2E
=
Note that this changes is incompatible in that previous versions of darcs
can't handle a repo with a new-style rebase in progress and vice versa=2E =
This
is something we cannot avoid unless we keep all the old code around, which
would reap us us of most of the benefits we get from this change=2E
] =
[move more repo paths to D=2ER=2EPaths
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702165826
Ignore-this: 8d1d58ce13ee439349aaffd04d956dba
] =
[clean up imports in Darcs=2EPatch=2EIdent to avoid warnings
Ben Franksen <ben=2Efranksen@online=2Ede>**20180917115841
Ignore-this: 432ee51baa22ac2711e83bba3a24ef75
] =
[add class Ident to abstract over patches with an identity
Ben Franksen <ben=2Efranksen@online=2Ede>**20171029221412
Ignore-this: 4fc76e8ecaca72ffc59c9f54e0444788
=
This change is a preparation for the addition of identifiers to prim
patches, so we can use the same algorithms for them=2E
] =
[added foldRL_M, foldwFL, and foldwRL, renamed foldlFL/RL to foldFL/RL
Ben Franksen <ben=2Efranksen@online=2Ede>**20171101004239
Ignore-this: 36ac70895a164b1f81af8cbd463b20a
=
First, the renamings (removing the 'l') have been made because (a) the nam=
e
is wrong for RL, which is actually right associative, and (b) because thes=
e
are both the "natural" folds, i=2Ee=2E the ones that replace the cons oper=
ator
with a function=2E
=
The other functions aren't used, yet, but will be used in the upcoming
addition of RepoPatchV3=2E The 'w' variants allow the transformation of
witnessed values, they are similar to foldRL/FL_M just not monadic=2E
] =
[layout fixes and a trivial refactor in D=2ET=2EP=2ECheck
Ben Franksen <ben=2Efranksen@online=2Ede>**20180915075933
Ignore-this: 453ec8305f86cd2fe939c7b7d51f1c4d
] =
[move mergeEitherWayValid from V1Set1 to Generic
Ben Franksen <ben=2Efranksen@online=2Ede>**20180502071708
Ignore-this: 2c925f24883f80cfe7b6e0e2bc91b57e
] =
[fix comment and remove out-commented code in D=2ET=2EP=2EA=2EPrimFileUUID
Ben Franksen <ben=2Efranksen@online=2Ede>**20180502065405
Ignore-this: dc1ca6f29eae22a0142fea3f16cd87d2
] =
[reformat parts of D=2ET=2EP=2EArbitrary=2EGeneric to avoid overlong lines
Ben Franksen <ben=2Efranksen@online=2Ede>**20180502065049
Ignore-this: b452772137b0382324ff993713766a0
] =
[document laziness of commuter functions and slightly improve commuterRLFL
Ben Franksen <ben=2Efranksen@online=2Ede>**20180911184016
Ignore-this: 34e7f8b5428b88321be57de62093f869
=
The result lists of commuterRLFL are now produced in an alternating fashio=
n,
so that both can be consumed lazily (from head to tail)=2E
] =
[make Commute a superclass of CommuteNoConflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20180911220005
Ignore-this: 1b0320b60ba26eb2638dd5848589d239
] =
[make CommuteNoConflicts a superclass of PrimPatch
Ben Franksen <ben=2Efranksen@online=2Ede>**20180908165001
Ignore-this: 722e6ad73533f93801d5437ff2dcd4f8
=
This allows to use mergeNoConflicts for prim patches=2E An alternative wou=
ld
be to scrap CommuteNoConflicts and instead add commuteNoCnflicts to the
Commute class=2E
] =
[use generic commuter functions to scrap boilerplate
Ben Franksen <ben=2Efranksen@online=2Ede>**20180908143225
Ignore-this: 2c538f1c8f85f79709fe21a05fc00242
] =
[factor CommuteNoConflicts to its own module
Ben Franksen <ben=2Efranksen@online=2Ede>**20180908111336
Ignore-this: c9bc4844fa5d5d9008a9628ca067f4e0
=
Also improved the documentation for it and for mergeNoConflicts=2E
] =
[replace D=2EUI=2EC=2EUtil=2ErepoTags with D=2EP=2ESet=2EpatchSetTags
Ben Franksen <ben=2Efranksen@online=2Ede>**20180718224724
Ignore-this: e6d6c3babd5ad98051284c7f4f9582b6
=
Also remove unused functions 'tags' and 'patchSetfMap' from D=2EP=2ESet=2E
] =
[avoid access to PatchSet constructors where possible
Ben Franksen <ben=2Efranksen@online=2Ede>**20180611181705
Ignore-this: b7f88c9dccf9f50ed35824b06d452882
=
This includes the full UI subsystem but also parts of Patch and Repository=
=2E
] =
[moved inOrderTags from convert command to D=2EP=2ESet
Ben Franksen <ben=2Efranksen@online=2Ede>**20180611171952
Ignore-this: ec6700455ba8bb3d51f0190c6bbdb748
] =
[replace our rmRecursive with removeDirectoryRecursive from directory packa=
ge
Ben Franksen <ben=2Efranksen@online=2Ede>**20180901093655
Ignore-this: 95f9308013bf8a20ab4081d240f6db7
=
This function has been fixed not to follow symbolic links since
directory-1=2E2=2E2=2E0, so we no longer need to roll our own=2E
] =
[replace most calls to getDirectoryContent with listDirectory
Ben Franksen <ben=2Efranksen@online=2Ede>**20180715124309
Ignore-this: 7917d3ab42a320fe8ef6611a2ecafc98
=
This function has been around since directory-1=2E2=2E5=2E0 (we currently =
require
at least 1=2E2=2E7)=2E Using it lets us avoid manually filtering out "=2E"=
and "=2E=2E"
entries=2E
] =
[improve docs for crudeSift and v1siftForPending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180827165549
Ignore-this: 18a6434d795d72bb5cbc7e49dd4c1405
] =
[simplify v1siftForPending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180827165528
Ignore-this: ad28511cb3e006aaec594fc505a67980
=
Using the Maybe monad here is completely unnecessary=2E
] =
[simplify definition of local function sift
Ben Franksen <ben=2Efranksen@online=2Ede>**20180827165039
Ignore-this: a0aac43bf64c452c789b38e9a5fc2bbc
] =
[move code from D=2EP=2EPrim=2ESift to D=2EP=2EPrim=2EV1
Ben Franksen <ben=2Efranksen@online=2Ede>**20180827093641
Ignore-this: be2dd09f9b9003632e7ed182b02be74f
] =
[treeDiff: abbreviate 'anchorPath ""' with a local function
Ben Franksen <ben=2Efranksen@online=2Ede>**20180828091242
Ignore-this: bed0e8761895410a5423d96dea0488ba
] =
[add comment to explain how treeDiff handles file vs=2E subtree removals
Ben Franksen <ben=2Efranksen@online=2Ede>**20180826172551
Ignore-this: ad166f87bcfc6d37901a7f7ed1844cea
] =
[consistent naming for "working tree"
raichoo@googlemail=2Ecom**20180716163939
Ignore-this: c2ad7855940a5d4b1f96039b5c2913e2
] =
[avoid warning in D=2ER=2EState on non-Windows OS
Ben Franksen <ben=2Efranksen@online=2Ede>**20180825084425
Ignore-this: ae818ac8646082bbfd4cd1c172e3455
] =
[tightened repo witnesses to demand wR~wT for more functions in in D=2ER=2E=
State
Ben Franksen <ben=2Efranksen@online=2Ede>**20180825091243
Ignore-this: e3eff4f91c0ee52fa8d075b481d67531
=
This started out with readPending and propagates to
readPendingAndMovesAndUnrecorded, readUnrecorded, readUnrecordedFiltered,
readRecordedAndPending, readIndex, updateIndex, getMoves=2E Requires a sma=
ll
code change in finalizeRepositoryChanges and a corresponding tightening in
D=2ER=2ERepair=2EcheckIndex=2E
] =
[fix docs for finalizeRepositoryChanges
Ben Franksen <ben=2Efranksen@online=2Ede>**20180825090512
Ignore-this: a8c0fc990ce726cd171893832e88d935
] =
[fix and simplify checkUnrecordedConflicts and then inline
Ben Franksen <ben=2Efranksen@online=2Ede>**20180722122446
Ignore-this: 62da36f754c62647520b0cb1f2f0f592
=
The implementation in checkUnrecordedConflicts really only checked for
conflicts with pending, but we need to check for conflicts with pending an=
d
working; and the merge that gives us this information has already been
calculated in tentativelyMergePatches: all new conflicts are contained in
them'' and new conflicts with pending and working are contained in pw'=2E
=
Also, when tentativelyMergePatches is called by a remote apply (during
execution of a push command), there is no interactive stdin, so promptYorn
throws an exception, which is now cought=2E This fixes an existing bug tha=
t
was hidden because the prompting happened only for conflicts with the remo=
te
pending, whereas it now happens for all conflicts with unrecorded changes=
=2E
] =
[in D=2ER=2EResolution, throw an error if cleanly merging conflict resoluti=
ons fails
Ben Franksen <ben=2Efranksen@online=2Ede>**20180604154921
Ignore-this: aeae746a8b3a681d6bd1acd2d330ed4
=
This is clearly an internal error and should be handled as such=2E It was
previously ignored by silently dropping the patch that could not be merged=
=2E
] =
[resolve issue2594: add UseIndex parameter to addToPending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180719171008
Ignore-this: 2c0f949e4b95af39807ec2fca8ac2255
] =
[fix: must not siftForPending in revertPending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180719171004
Ignore-this: 53c02a5e44597eb90b772b7c9debc32d
=
The reason is that we want the checks that attempt to apply pending to
pristine to fail as early as possible and also consistently regardless of
whether we are in a transaction or not=2E If we siftForPending with a bugg=
y
pending such as constructed in tests/pending_has_conflicts=2Esh applyToTre=
e no
longer fails=2E
] =
[accept issue2594: darcs show index crashes replace with unrecorded force h=
unk
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702140939
Ignore-this: 73ac92ef41ab16c811453bb2d827f71c
] =
[no longer lie about repo witnesses
Ben Franksen <ben=2Efranksen@online=2Ede>**20180719170744
Ignore-this: b689ab3e73b43e13977bb157669aa3b2
=
In particular, this means that most of the procedures in D=2ER=2EState now
require that the recorded and the tentative state coincide, so that readin=
g
the recorded state is justified even if we are in a "transaction" i=2Ee=2E
revertRepositoryChanges has been called (via withRepoLock)=2E Also,
finalizeRepositoryChanges now returns a properly casted Repository=2E
=
We now track the Repository token using a single local variable that gets
shadowed by each successive "update"=2E This makes it impossible to
accidentally use an old version=2E To avoid warnings, these variables are
prefixed with an underscore=2E
] =
[simplify readRecorded and readPending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180619204359
Ignore-this: 1ffe804603dc34fc1793c3cc8638d173
=
=2E=2E=2Eusing peekPristineHash and the new D=2ER=2EPaths module=2E
] =
[define repo paths in a separate module
Ben Franksen <ben=2Efranksen@online=2Ede>**20180619203930
Ignore-this: 4096a66894bd124171161508c4c1fa6c
] =
[move applyToTentativePristine to before repo changes
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702131930
Ignore-this: 5695f7a39381cf488c7054687bf2fcdf
=
This is pure code aesthetics=2E The call gets the original r (Repository)
passed, so it looks better if we make it before we call the functions that
return the new (coerced) Repository=2E
] =
[explain how tentativelyMergePatches works
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702131923
Ignore-this: 29c052902fade67f56b241acf4dc63a0
=
This patch also renames a few local variables in this function=2E
] =
[resolve issue2592: update pending with coalesced look-for changes
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702163803
Ignore-this: 433b715f2787c1199c4309581eb1ea36
] =
[simplified setTentativePending and fix its type witnesses
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702145112
Ignore-this: a20b32a92265091a1d81c9d963949cd1
] =
[make D=2ER=2EPending=2Eprepend more type safe (by removing it)
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702145101
Ignore-this: 4dd145953c7168603ca8a3694c9109ec
=
This function coerced witnesses and had corresponding warnings attached=2E=
The
need for coercing was that it reads the pending patch and also writes it
back with some changes that were removed from the repo prepended=2E If we
split this action up and read pending before adding the patches to the rep=
o
and afterwards write the pending, then the witnesses all match up just fin=
e=2E
This requires removeFromTentativeInventory to return a repo with
appropriately coerced witnesses=2E
The cost of this operation is that we must export read/writeTentativePendi=
ng=2E
] =
[fix handling of pending patch in amend command
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702134008
Ignore-this: 4f95452e8c4bdc28cd3ed20be14f0035
=
In case of look-for-moves/replaces, the code called
tentativelyRemoveFromPending on the old patch=2E This was done after
tentativelyRemovePatch and tentativelyAddPatch had already adapted the
pending patch (via YesUpdatePending)=2E This is clearly wrong and worked o=
nly
because tentativelyRemovePatches called prepend, which pre-filtered the ne=
w
prim patches with crudeSift=2E This is no longer done, and so we now get
failures when we try to apply pending=2E
=
The clean solution is to pass NoUpdatePending to both tentativelyRemovePat=
ch
and tentativelyAddPatch and then adapt pending in one go with the differen=
ce
between old and new patch=2E The function tentativelyRemoveFromPending now
takes an FL of prim patches, has more correct type witnesses, uses less
coercion, and has its UpdatePending parameter removed=2E
=
This restores the regression of issue2209-look_for_replaces after the fix
for issue2548-inconsistent-pending=2E It also makes the previously failing
test look_for_replaces1 succeed=2E
] =
[accept issue2592: unclean pending with look-for options
Ben Franksen <ben=2Efranksen@online=2Ede>**20180618190530
Ignore-this: 7d3d1d113694143bde626d0d8ed3a5ed
] =
[remove UpdatePending parameter from tentativelyAddToPending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702143403
Ignore-this: 49e37e39bbac54cfdff71900c3a6416a
=
All call sites passed YesUpdatePending, literally=2E
] =
[add revertPending to complement finalizePending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702141814
Ignore-this: b9175e36e417254dede371d6573c6dcf
] =
[removed UpdatePending parameter from a few functions
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702131536
Ignore-this: 137a392994f408bcd843ce4deb5b0487
=
Affected are setTentativePending, prepend, the functions in D=2ER=2EMerge,
addToPending, and addPendingDiffToPending=2E The parameter could be remove=
d
because either all call sites passed YesUpdatePending (literally), or the
same or closely related case distinction was already done at the call site=
=2E
] =
[rename UpdateWorking to UpdatePending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180702131409
Ignore-this: b32c179994ff299dfc1598bab875b454
=
The name of this type (and the parameter names) now reflect what it does,
namely configure for certain calls whether the pending patch should be
updated or not=2E
] =
[remove writePatchSet and patchSetToRepository from D=2ER=2EClone
Ben Franksen <ben=2Efranksen@online=2Ede>**20180610151003
Ignore-this: a6c059b9450839f7ac46f0524f93e4dd
=
patchSetToRepository was already commented out and writePatchSet was used
only in D=2EUI=2ECommands=2ERepair, where the relevant parts are now inlin=
ed=2E Also
did some refactorings there while we're at it=2E
] =
[move filterNonInternal from tag command to D=2EP=2EMatch
Ben Franksen <ben=2Efranksen@online=2Ede>**20180611173502
Ignore-this: ad9429c268fdb84055c681e4500accfc
] =
[move matchingHead to D=2EP=2EMatch, move contextPatches to D=2EP=2EDepends
Ben Franksen <ben=2Efranksen@online=2Ede>**20180611171139
Ignore-this: d9560cc892e65e5a2ac6244df9bbc6d5
] =
[simplify return type of splitOnTag
Ben Franksen <ben=2Efranksen@online=2Ede>**20180611102459
Ignore-this: a724190d1f45336cd4e538377a3e5a87
=
Instead of returning a PatchSet with an empty trailing list of patches plu=
s
trailing patches separately, we as well return just a PatchSet and put the
trailig patches back=2E
] =
[refactor matching of PatchSets
Ben Franksen <ben=2Efranksen@online=2Ede>**20180609222350
Ignore-this: 8263b213cb129ade39454183349f9361
=
This affects the commands annotate, clone, diff, dist, show contents, and
show files=2E For these, selecting a single patch or a range of patches ma=
kes
no sense; instead matching means to select the version (PatchSet) consisti=
ng
of all patches up to (including) the latest matching patch, except for --t=
ag
where we get the exact version corresponding to the tag=2E
=
The functions findAPatch and matchPatch and the data type
InclusiveOrExclusive are now obsolete have been removed=2E Other functions=
are
superseded: getPatchesBeyondTag is replaced by the more general
splitOnMatchingTag; getTagS and getMatcherS have been inlined into
getNonrangeMatchS, which has been renamed to rollbackToPatchSetMatch;
havePatchsetMatch is replaced by patchSetMatch=2E The new data type
PatchSetMatch precisely captures the different ways to match a PatchSet;
patchSetMatch returns it and rollbackToPatchSetMatch and getOnePatchSet ta=
ke
it as argument=2E Also, getNonrangeMatch is now called getRecordedUpToMatc=
h,
and dropn is renamed to patchSetDrop and exported=2E
=
There are now separate DarcsFlags and MatchFlags for --index=3DN (OneIndex=
)
versus --index=3DN-M (MatchIndexRange), which streamlines index matching=
=2E
] =
[make spanRL lazy, add takeWhileRL
Ben Franksen <ben=2Efranksen@online=2Ede>**20180609222232
Ignore-this: 4bd05d0fc5146aac6be7934056d18716
] =
[inlined a where clause in splitOnTag
Ben Franksen <ben=2Efranksen@online=2Ede>**20180609221946
Ignore-this: df78934f07e25f690a9839073f96d1ef
] =
[simplify D=2EP=2EMatch=2EmatchExists
Ben Franksen <ben=2Efranksen@online=2Ede>**20180609142356
Ignore-this: 6b66004d0117c5256a30f5defbfa22f5
] =
[removed unsused (incl=2E darcsden) function getFirstMatchS
Ben Franksen <ben=2Efranksen@online=2Ede>**20180609121825
Ignore-this: 1dc69395d33727eaaab76ed6525102c4
] =
[simplify D=2ER=2EHashed=2EreorderInventory
Ben Franksen <ben=2Efranksen@online=2Ede>**20180608093343
Ignore-this: 2d59b83971455f2f76a51fddc48028dc
=
This gets rid of the last use of tentativelyReplacePatches which has been
removed=2E Instead of removing patches from the repo and then adding them
back, we directly write the new patchset=2E tentativelyReplacePatches filt=
ered
out the rebase patch from the patches it removes=2E This was brittle and a=
lso
unnecessary: we can assume the rebase patch is not covered by any tag and
thus automatically belongs to the untagged tail of patches=2E
=
Finding the latest tag and cleaning it is now optimized by using the new
utility function breakRL=2E This avoids searching for the latest tag twice
(first in misplacedPatches and then again in splitOnTag)=2E The fused
functionality is now in function D=2EP=2EDepends=2EcleanLatestTag=2E
=
The test for darcs optimize has been enhanced to actually test that optimi=
ze
reorder does what it should=2E
] =
[add class PrimSift so we can avoid using PrimConstruct and PrimClassify in=
Pending
Ben Franksen <ben=2Efranksen@online=2Ede>**20180505065806
Ignore-this: a236357241048ec8e0eb26a99250bedb
] =
[move tryShrinkingInverse to D=2EP=2EInvert, rename to dropInverses
Ben Franksen <ben=2Efranksen@online=2Ede>**20180301225601
Ignore-this: 8dc5633d478d66135dfa2f36898edc7f
=
The function is defined solely in terms of Invert and Eq2=2E
] =
[remove commuteFLorComplain and replace with commuteFL
Ben Franksen <ben=2Efranksen@online=2Ede>**20180516074050
Ignore-this: 22c884f446084a9a87abe9175db1e817
=
The extra information provided by commuteFLorComplain was nowhere used=2E
] =
[respect verbosity options in amend command
Ben Franksen <ben=2Efranksen@online=2Ede>**20180713170751
Ignore-this: 47054467ad82cadc305e6373154d11db
] =
[add/change some comments in optimize upgrade command
Ben Franksen <ben=2Efranksen@online=2Ede>**20180612174221
Ignore-this: 2411d122f587c7d49a9b12f38f1ce182
] =
[export getPrefLines for darcsden
Ben Franksen <ben=2Efranksen@online=2Ede>**20180609112943
Ignore-this: b5c24b98188f95c845c680e418c889de
] =
[use +<<+ in D=2EP=2ESet=2EappendPSFL
Ben Franksen <ben=2Efranksen@online=2Ede>**20180608120457
Ignore-this: 932a5ac2ba0aa305746698d9212ffe85
] =
[remove method anIdentity from PrimConstruct
Ben Franksen <ben=2Efranksen@online=2Ede>**20180501154124
Ignore-this: 2a4afd0048567d73c35245274c286ec7
=
This method was used only in the test harness to extract pairs and triples
of adjacent patches from an arbitrary patch tree, in case the tree does no=
t
contain enough patches=2E Rather than conjuring meaningless patches out of
thin air, a better solution is to reject starting states with not enough
patches=2E Along the way, some unused functions and instances in the test
harness were deleted=2E
] =
[add laws to classes Commute and CommuteNoConflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20180607195130
Ignore-this: 9b2be35019e7b0210db0eaaf4a85f4a1
] =
[replace naturalMerge with mergeNoConflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20180607181432
Ignore-this: 7a4b0793074bb3be28a8693100d2978b
=
This change is a consequence of my improved understanding of what
commuteNoConflicts is about and how non-conflicting merge should work, see
the haddocks for details=2E The new function is also more efficient becaus=
e
(a) commuteNoConflicts has to consider fewer cases and (b) we can now drop
the extra commute check on the result of the merge=2E
] =
[in D=2EP=2EV1=2ECommute, remove commuteNoMerger and replace with commuteNo=
Conflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20180604154812
Ignore-this: 52691e31f7822683c67d1768a94bcbe4
] =
[simplify V1 merge by calculating both branches in one go
Ben Franksen <ben=2Efranksen@online=2Ede>**20180530163134
Ignore-this: ba1d3de13df7724f5aeec898e8cb5915
] =
[factor swapMerge from D=2EP=2EV2=2ERepoPatch to D=2EP=2EMerge
Ben Franksen <ben=2Efranksen@online=2Ede>**20180530163032
Ignore-this: 4492404a94fe2704aad86c0fdded992c
] =
[refactor the instance Commute RepoPatchV2
Ben Franksen <ben=2Efranksen@online=2Ede>**20180529130151
Ignore-this: e58fe2aad17250793d1f4b38e9fbbb90
=
To avoid repeated calls to commuteNoConflicts in cases where we know it wi=
ll
fail, add commuteConflicting as a separate top-level function=2E Also fact=
or
out invertCommuter which is now used for both commuteConflicting and
commuteNoConflicts=2E
] =
[improved haddocks for CommuteNoConflicts
Ben Franksen <ben=2Efranksen@online=2Ede>**20180529125540
Ignore-this: 66fd77d34e106b6edd693193e9e02771
] =
[remove out-commented code line from mangleUnravelledHunks
Ben Franksen <ben=2Efranksen@online=2Ede>**20180426071255
Ignore-this: 7116db02cb6ab3b75b392aafbdbcbec
] =
[add haddocks for D=2EP=2EConflict=2EIsConflictedPrim
Ben Franksen <ben=2Efranksen@online=2Ede>**20180426071209
Ignore-this: 1c66041eff309d484cfbbb3ead0d2867
] =
[rename 'conflictedEffect' to 'isConflicted'
Ben Franksen <ben=2Efranksen@online=2Ede>**20180426070037
Ignore-this: 59ea355b5af257a5be76236361107be0
=
This function (class method) is used to classify patches and has nothing t=
o
do with the effect of a patch=2E
] =
[apply hunks for the same file in one go for V2, too
Ben Franksen <ben=2Efranksen@online=2Ede>**20180216111952
Ignore-this: 6cf6e1421a30221c95762a02f0869f09
=
It seems this optimization was never done for RepoPatchV2=2E
] =
[rebase: use die instead of error
raichoo@googlemail=2Ecom**20180614072937
Ignore-this: 320248b9c073e02491762d83ef704cec
] =
[support containers 0=2E6=2Ex
Ganesh Sittampalam <ganesh@earth=2Eli>**20180622115811
Ignore-this: cec9331750943804a68430ff5d177321
] =
[fix issue1857 test on Windows
Ganesh Sittampalam <ganesh@earth=2Eli>**20180610184054
Ignore-this: 6fc9b0a9ee752b0e615cbe82fef20776
] =
[support QuickCheck 2=2E11
Ganesh Sittampalam <ganesh@earth=2Eli>**20180609153034
Ignore-this: 13b7a0fa536221ade5575148670d8b7c
] =
[TAG 2=2E14=2E0
Guillaume Hoffmann <guillaumh@gmail=2Ecom>**20180404143457
Ignore-this: b65f09f1e7a78e00ba98e63108be2833
] =
Patch bundle hash:
b613b2ca9857462d174839345095eea571503b78
--=_--
.
Attachments
|