darcs-beta-2.7.98.1: a distributed, interactive, smart revision control system

Darcs.Patch.V2.Non

Description

NonPatch and Non patches are patches that store a context as a sequence of patches. See Darcs.Patch.Real for example usage.

Synopsis

Documentation

data Non p x whereSource

Non stores a context with a Prim patch.

Constructors

Non :: FL p a x -> PrimOf p x y -> Non p a 

Instances

(Show2 p, Show2 (PrimOf p)) => Show1 (Non p) 
(Commute p, MyEq p, MyEq (PrimOf p)) => Eq (Non p x) 
(Show2 p, Show2 (PrimOf p)) => Show (Non p x) 

class Nonable p whereSource

Methods

non :: p x y -> Non p xSource

Instances

PrimPatch prim => Nonable (RealPatch prim) 

unNon :: FromPrim p => Non p x -> Sealed (FL p x)Source

Return as a list the context followed by the primitive patch.

add :: (WL l, Patchy p, ToFromPrim p) => l (PrimOf p) x y -> Non p y -> Non p xSource

addP :: (Patchy p, ToFromPrim p) => p x y -> Non p y -> Non p xSource

addP x cy tries to commute x past cy and always returns some variant cy'. -- commutation suceeds, the variant is just straightforwardly the commuted versian. If commutation fails, the variant consists of x prepended to the context of cy.

remP :: (Patchy p, ToFromPrim p) => p x y -> Non p x -> Maybe (Non p y)Source

addPs :: (Patchy p, ToFromPrim p) => RL p x y -> Non p y -> Non p xSource

addPs xs cy commutes as many patches of xs past cy as possible, stopping at the first patch that fails to commute. Note the fact xs is a RL

Suppose we have

 x1 x2 x3 [c1 c2 y]

and that in our example c1 fails to commute past x1, this function would commute down to

 x1 [c1'' c2'' y''] x2' x3'

and return [x1 c1'' c2'' y'']

remPs :: (Patchy p, ToFromPrim p) => FL p x y -> Non p x -> Maybe (Non p y)Source

remNons :: (Nonable p, Effect p, Patchy p, ToFromPrim p, PrimPatchBase p, MyEq (PrimOf p)) => [Non p x] -> Non p x -> Non p xSource

(*>) :: (Patchy p, ToFromPrim p) => Non p x -> p x y -> Maybe (Non p y)Source

(>*) :: (Patchy p, ToFromPrim p) => p x y -> Non p y -> Maybe (Non p x)Source

(*>>) :: (WL l, Patchy p, ToFromPrim p, PrimPatchBase p) => Non p x -> l (PrimOf p) x y -> Maybe (Non p y)Source

(>>*) :: (WL l, Patchy p, ToFromPrim p) => l (PrimOf p) x y -> Non p y -> Maybe (Non p x)Source

propAdjustTwice :: (Patchy p, ToFromPrim p, MyEq (PrimOf p)) => p x y -> Non p y -> Maybe DocSource