darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Darcs.Patch.V3.Contexted

Description

Contexted patches.

Synopsis

Contexted patches

data Contexted p wX Source #

Instances

Instances details
Show2 p => Show1 (Contexted p) Source # 
Instance details

Defined in Darcs.Patch.V3.Contexted

Methods

showDict1 :: Dict (Show (Contexted p wX)) Source #

Show2 p => Show (Contexted p wX) Source # 
Instance details

Defined in Darcs.Patch.V3.Contexted

Methods

showsPrec :: Int -> Contexted p wX -> ShowS #

show :: Contexted p wX -> String #

showList :: [Contexted p wX] -> ShowS #

Ident p => Eq (Contexted p wX) Source #

Equality between Contexted patches reduces to equality of the identifiers of the patches referred to if we look at them from the same context. (This assumes witnesses aren't coerced in an unsafe manner.)

Instance details

Defined in Darcs.Patch.V3.Contexted

Methods

(==) :: Contexted p wX -> Contexted p wX -> Bool #

(/=) :: Contexted p wX -> Contexted p wX -> Bool #

Ident p => Ord (Contexted p wX) Source # 
Instance details

Defined in Darcs.Patch.V3.Contexted

Methods

compare :: Contexted p wX -> Contexted p wX -> Ordering #

(<) :: Contexted p wX -> Contexted p wX -> Bool #

(<=) :: Contexted p wX -> Contexted p wX -> Bool #

(>) :: Contexted p wX -> Contexted p wX -> Bool #

(>=) :: Contexted p wX -> Contexted p wX -> Bool #

max :: Contexted p wX -> Contexted p wX -> Contexted p wX #

min :: Contexted p wX -> Contexted p wX -> Contexted p wX #

Query

ctxId :: Ident p => Contexted p wX -> PatchId p Source #

Identity of a contexted patch.

ctxView :: Contexted p wX -> Sealed ((FL p :> p) wX) Source #

We sometimes want to pattern match on a Contexted patch but still guard against violation of the invariants. So we export a view that is isomorphic to the Contexted type but doesn't allow to manipulate the internals.

ctxNoConflict :: (CleanMerge p, Commute p, Ident p) => Contexted p wX -> Contexted p wX -> Bool Source #

Contexted patches conflict with each other if the identity of one is in the context of the other or they cannot be merged cleanly.

ctxToFL :: Contexted p wX -> Sealed (FL p wX) Source #

Convert a Contexted patch into a plain FL with the patch at the end.

ctxDepends :: Ident p => Contexted p wX -> Contexted p wX -> Bool Source #

Wether the first argument is contained (identity-wise) in the context of the second, in other words, the second depends on the first. This does not include equality, only proper dependency.

Construct / Modify

ctx :: p wX wY -> Contexted p wX Source #

A Contexted patch with empty context.

ctxAdd :: (Commute p, Invert p, Ident p) => p wX wY -> Contexted p wY -> Contexted p wX Source #

Add a patch to the context of a Contexted patch. This is the place where we take care of the invariants.

ctxAddRL :: (Commute p, Invert p, Ident p) => RL p wX wY -> Contexted p wY -> Contexted p wX Source #

Add an RL of patches to the context.

ctxAddInvFL :: (Commute p, Invert p, Ident p) => FL p wX wY -> Contexted p wX -> Contexted p wY Source #

Add an FL of patches to the context but invert it first.

ctxAddFL :: (Commute p, Invert p, Ident p) => FL p wX wY -> Contexted p wY -> Contexted p wX Source #

Add an FL of patches to the context.

commutePast :: Commute p => p wX wY -> Contexted p wY -> Maybe (Contexted p wX) Source #

(Definition 10.2) Commute a patch past a Contexted patch. This commutes it past the context and then past the patch itself. If it succeeds, the patch that we commuted past gets dropped. Note that this does not succeed if the inverted patch is in the Contexted patch.

commutePastRL :: Commute p => RL p wX wY -> Contexted p wY -> Maybe (Contexted p wX) Source #

Not defined in the paper but used in the commute algorithm.

PatchInspect helpers

ReadPatch and ShowPatch helpers

Properties

prop_ctxInvariants :: (Commute p, Invert p, SignedIdent p) => Contexted p wX -> Bool Source #

This property states that no prefix of the context commutes with the rest of the Contexted patch and that the context never contains a patch and its inverse.

prop_ctxEq :: (Commute p, Eq2 p, Ident p) => Contexted p wX -> Contexted p wX -> Bool Source #

This property states that equal Contexted patches have equal content up to reorderings of the context patches.

prop_ctxPositive :: SignedIdent p => Contexted p wX -> Bool Source #

This property states that patches in the context of a Contexted patch as well as the patch itself are positive. It does not necessarily hold for all Contexted patches.