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

Darcs.Patch.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

type NonPatch = Non PrimSource

Convenience type for non primitive patches

data Non p whereSource

Non stores a context with a Prim patch.

Constructors

Non :: FL p -> Prim -> Non p 

Instances

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

class Nonable p whereSource

Methods

non :: p -> Non pSource

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

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

readNon :: (ReadPatch p, ParserM m) => m (Maybe (Non p))Source

showNons :: ShowPatch (FL p) => [Non p] -> DocSource

readNons :: (ReadPatch p, ParserM m) => m [Non p]Source

add :: (Effect q, Patchy p, ToFromPrim p) => q -> Non p -> Non pSource

rem :: (Effect q, Patchy p, ToFromPrim p) => q -> Non p -> Maybe (Non p)Source

addP :: (Patchy p, ToFromPrim p) => p -> Non p -> Non pSource

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 -> Non p -> Maybe (Non p)Source

addPs :: (Patchy p, ToFromPrim p) => RL p -> Non p -> Non pSource

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 -> Non p -> Maybe (Non p)Source

remAddP :: (Patchy p, ToFromPrim p) => p -> Non p -> Non pSource

remAddPs :: (Patchy p, ToFromPrim p) => RL p -> Non p -> Non pSource

remNons :: (Nonable p, Effect p, Patchy p, ToFromPrim p, ShowPatch p) => [Non p] -> Non p -> Non pSource

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

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

(*>>) :: (Effect q, Patchy q, Patchy p, ToFromPrim p) => Non p -> q -> Maybe (Non p)Source

(>>*) :: (Effect q, Patchy p, ToFromPrim p) => q -> Non p -> Maybe (Non p)Source