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

Safe HaskellNone

Darcs.Patch.V2.Non

Synopsis

Documentation

data Non p x whereSource

A Non stores a context with a Prim patch. It is a patch whose effect isn't visible - a Non-affecting patch.

Constructors

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

Instances

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

Nons are equal if their context patches are equal, and they have an equal prim patch.

(Show2 p, Show2 (PrimOf p)) => Show (Non p x) 

class Nonable p whereSource

Nonable represents the class of patches that can be turned into a Non.

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

unNon converts a Non into a FL of its context followed by the primitive patch.

showNon :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => Non p x -> DocSource

showNon creates a Doc representing a Non.

showNons :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => [Non p x] -> DocSource

showNons creates a Doc representing a list of Nons.

readNon :: (ReadPatch p, PatchListFormat p, PrimPatchBase p, ParserM m) => m (Non p x)Source

readNon is a parser that attempts to read a single Non.

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

readNons is a parser that attempts to read a list of Nons.

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

commutePrimsOrAddToCtx takes a WL of prims and attempts to commute them past a Non.

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

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

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

commuteOrRemFromCtx attempts to remove a given patch from a Non. If the patch was not in the Non, then the commute will succeed and the modified Non will be returned. If the commute fails then the patch is either in the Non context, or the Non patch itself; we attempt to remove the patch from the context and then return the non with the updated context.

TODO: understand if there is any case where p is equal to the prim patch of the Non, in which case, we return the original Non, is that right?

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

commuteOrAddToCtxRL xs cy commutes as many patches of xs past cy as possible, adding any that don't commute to the context of cy. Suppose we have

 x1 x2 x3 [c1 c2 y]

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

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

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

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

commuteOrRemFromCtxFL attempts to remove a FL of patches from a Non, returning Nothing if any of the individual removes fail.

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

(*>) attemts to modify a Non by commuting it past a given patch.

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

(>*) attempts to modify a Non, by commuting a given patch past it.

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

(*>>) attempts to modify a Non by commuting it past a given WL of patches.

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

(>>*) attempts to modify a Non by commuting a given WL of patches past it.