darcs-2.16.3: a distributed, interactive, smart revision control system

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.Ident

Contents

Synopsis

Documentation

class Ord (PatchId p) => Ident p where Source #

Class of patches that have an identity.

It generalizes named prim patches a la camp (see Darcs.Patch.Prim.Named) and Named patches i.e. those with a PatchInfo.

Patch identity should be invariant under commutation: if there is also an instance Commute p, then

commute (p :> q) == Just (q' :> p') => ident p == ident p' && ident q == ident q'

The converse should also be true: patches with the same identity can be commuted (back) to the same context and then compare equal. Assuming

  p :: p wX wY, (ps :> q) :: (RL p :> p) wX wZ

then

ident p == ident q => commuteRL (ps :> q) == Just (p :> _)

As a special case we get that parallel patches with the same identity are equal: if p :: p wX wY, q :: p wX wZ, then

ident p == ident q => p =\/= q == IsEq

In general, comparing patches via their identity is coarser than (structural) equality, so we only have

unsafeCompare p q => (ident p == ident q)

Methods

ident :: p wX wY -> PatchId p Source #

Instances
Ident (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

ident :: Named p wX wY -> PatchId (Named p) Source #

Ident (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Methods

ident :: RebaseChange prim wX wY -> PatchId (RebaseChange prim) Source #

Ident p => Ident (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Methods

ident :: Invertible p wX wY -> PatchId (Invertible p) Source #

Ident (PatchInfoAndG rt p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

ident :: PatchInfoAndG rt p wX wY -> PatchId (PatchInfoAndG rt p) Source #

Ident (WrappedNamed rt p) Source # 
Instance details

Defined in Darcs.Patch.Named.Wrapped

Methods

ident :: WrappedNamed rt p wX wY -> PatchId (WrappedNamed rt p) Source #

SignedId name => Ident (PrimWithName name p) Source # 
Instance details

Defined in Darcs.Patch.Prim.WithName

Methods

ident :: PrimWithName name p wX wY -> PatchId (PrimWithName name p) Source #

SignedId name => Ident (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

ident :: RepoPatchV3 name prim wX wY -> PatchId (RepoPatchV3 name prim) Source #

type SignedIdent p = (Ident p, SignedId (PatchId p)) Source #

Constraint for patches that have an identity that is signed, i.e. can be positive (uninverted) or negative (inverted).

Provided that an instance Invert exists, inverting a patch inverts its identity:

ident (invert p) = invertId (ident p)

type family PatchId (p :: * -> * -> *) Source #

Instances
type PatchId (RepoPatchV1 prim) Source # 
Instance details

Defined in Darcs.Patch.V1.Core

type PatchId (RepoPatchV1 prim) = ()
type PatchId (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

type PatchId (RepoPatchV2 prim) = ()
type PatchId (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

type PatchId (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

type PatchId (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

type PatchId (NamedPrim p) Source # 
Instance details

Defined in Darcs.Patch.Prim.Named

type PatchId (PatchInfoAndG rt p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

type PatchId (WrappedNamed rt p) Source # 
Instance details

Defined in Darcs.Patch.Named.Wrapped

type PatchId (PrimWithName name p) Source # 
Instance details

Defined in Darcs.Patch.Prim.WithName

type PatchId (PrimWithName name p) = name
type PatchId (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

type PatchId (RepoPatchV3 name prim) = name

class Ord a => SignedId a where Source #

Signed identities.

Like for class Invert, we require that invertId is self-inverse:

invertId . invertId = id

We also require that inverting changes the sign:

positiveId . invertId = not . positiveId

Side remark: in mathematical terms, these properties can be expressed by stating that invertId is an involution and that positiveId is a "homomorphism of sets with an involution" (there is no official term for this) from a to the simplest non-trivial set with involution, namely Bool with the involution not.

Methods

positiveId :: a -> Bool Source #

invertId :: a -> a Source #

class StorableId a where Source #

Storable identities.

The methods here can be used to help implement ReadPatch and ShowPatch for a patch type containing the identity.

As with all Read/Show pairs, We expect that the output of showId ForStorage a can be parsed by readId to produce a.

class IdEq2 p where Source #

Faster equality tests for patches with an identity.

Minimal complete definition

Nothing

Methods

(=\^/=) :: p wA wB -> p wA wC -> EqCheck wB wC Source #

(=/^\=) :: p wA wC -> p wB wC -> EqCheck wA wB Source #

(=\^/=) :: Ident p => p wA wB -> p wA wC -> EqCheck wB wC Source #

(=/^\=) :: Ident p => p wA wC -> p wB wC -> EqCheck wA wB Source #

Instances
(Commute p, Ident p) => IdEq2 (FL p) Source #

The Commute requirement here is not technically needed but makes sense logically.

Instance details

Defined in Darcs.Patch.Ident

Methods

(=\^/=) :: FL p wA wB -> FL p wA wC -> EqCheck wB wC Source #

(=/^\=) :: FL p wA wC -> FL p wB wC -> EqCheck wA wB Source #

IdEq2 (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Methods

(=\^/=) :: Named p wA wB -> Named p wA wC -> EqCheck wB wC Source #

(=/^\=) :: Named p wA wC -> Named p wB wC -> EqCheck wA wB Source #

IdEq2 (PatchInfoAndG rt p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Methods

(=\^/=) :: PatchInfoAndG rt p wA wB -> PatchInfoAndG rt p wA wC -> EqCheck wB wC Source #

(=/^\=) :: PatchInfoAndG rt p wA wC -> PatchInfoAndG rt p wB wC -> EqCheck wA wB Source #

(SignedId name, Eq2 p) => IdEq2 (PrimWithName name p) Source # 
Instance details

Defined in Darcs.Patch.Prim.WithName

Methods

(=\^/=) :: PrimWithName name p wA wB -> PrimWithName name p wA wC -> EqCheck wB wC Source #

(=/^\=) :: PrimWithName name p wA wC -> PrimWithName name p wB wC -> EqCheck wA wB Source #

merge2FL :: (Commute p, Merge p, Ident p) => FL p wX wY -> FL p wX wZ -> (FL p :/\: FL p) wY wZ Source #

This function is similar to merge, but with one important difference: merge works on patches for which there is not necessarily a concept of identity (e.g. primitive patches, conflictors, etc). Thus it does not even try to recognize patches that are common to both sequences. Instead these are passed on to the Merge instance for single patches. This instance may handle duplicate patches by creating special patches (Duplicate, Conflictor).

We do not want this to happen for named patches, or in general for patches with an identity. Instead, we want to discard one of the two duplicates, retaining only one copy. This is done by the fastRemoveFL calls below. We call mergeFL only after we have ensured that the head of the left hand side does not occur in the right hand side.

fastRemoveFL :: forall p wX wY wZ. (Commute p, Ident p) => p wX wY -> FL p wX wZ -> Maybe (FL p wY wZ) Source #

Remove a patch from an FL of patches with an identity. The result is Just whenever the patch has been found and removed and Nothing otherwise. If the patch is not found at the head of the sequence we must first commute it to the head before we can remove it.

We assume that this commute always succeeds. This is justified because patches are created with a (universally) unique identity, implying that if two patches have the same identity, then they have originally been the same patch; thus being at a different position must be due to commutation, meaning we can commute it back.

fastRemoveRL :: forall p wX wY wZ. (Commute p, Ident p) => p wY wZ -> RL p wX wZ -> Maybe (RL p wX wY) Source #

Same as fastRemoveFL only for RL.

fastRemoveSubsequenceRL :: (Commute p, Ident p) => RL p wY wZ -> RL p wX wZ -> Maybe (RL p wX wY) Source #

findCommonFL :: (Commute p, Ident p) => FL p wX wY -> FL p wX wZ -> Fork (FL p) (FL p) (FL p) wX wY wZ Source #

Find the common and uncommon parts of two lists that start in a common context, using patch identity for comparison. Of the common patches, only one is retained, the other is discarded, similar to merge2FL.

commuteToPrefix :: (Commute p, Ident p) => Set (PatchId p) -> FL p wX wY -> Maybe ((FL p :> RL p) wX wY) Source #

Try to commute patches matching any of the PatchIds in the set to the head of an FL, i.e. backwards in history. It is not required that all the PatchIds are found in the sequence, but if they do then the traversal terminates as soon as the set is exhausted.

commuteToPostfix :: forall p wX wY. (Commute p, Ident p) => Set (PatchId p) -> RL p wX wY -> Maybe ((FL p :> RL p) wX wY) Source #

Try to commute patches matching any of the PatchIds in the set to the head of an RL, i.e. forwards in history. It is not required that all the PatchIds are found in the sequence, but if they do then the traversal terminates as soon as the set is exhausted.

commuteWhatWeCanToPostfix :: forall p wX wY. (Commute p, Ident p) => Set (PatchId p) -> RL p wX wY -> (FL p :> RL p) wX wY Source #

Like commuteToPostfix but drag dependencies with us.

Properties