Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Non p wX where
- class Nonable p where
- unNon :: FromPrim p => Non p wX -> Sealed (FL p wX)
- showNon :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => ShowPatchFor -> Non p wX -> Doc
- showNons :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => ShowPatchFor -> [Non p wX] -> Doc
- readNon :: (ReadPatch p, PatchListFormat p, PrimPatchBase p) => Parser (Non p wX)
- readNons :: (ReadPatch p, PatchListFormat p, PrimPatchBase p) => Parser [Non p wX]
- commutePrimsOrAddToCtx :: (WL l, Apply p, Commute p, Invert p, ToFromPrim p) => l (PrimOf p) wX wY -> Non p wY -> Non p wX
- commuteOrAddToCtx :: (Commute p, ToFromPrim p) => p wX wY -> Non p wY -> Non p wX
- commuteOrRemFromCtx :: (Commute p, Invert p, Eq2 p, ToFromPrim p) => p wX wY -> Non p wX -> Maybe (Non p wY)
- commuteOrAddToCtxRL :: (Apply p, Commute p, Invert p, ToFromPrim p) => RL p wX wY -> Non p wY -> Non p wX
- commuteOrRemFromCtxFL :: (Apply p, Commute p, Invert p, Eq2 p, ToFromPrim p) => FL p wX wY -> Non p wX -> Maybe (Non p wY)
- remNons :: (Nonable p, Effect p, Apply p, Commute p, Invert p, Eq2 p, ToFromPrim p, PrimPatchBase p) => [Non p wX] -> Non p wX -> Non p wX
- (*>) :: (Commute p, Invert p, ToFromPrim p) => Non p wX -> p wX wY -> Maybe (Non p wY)
- (>*) :: (Commute p, ToFromPrim p) => p wX wY -> Non p wY -> Maybe (Non p wX)
- (*>>) :: (WL l, Apply p, Commute p, Invert p, ToFromPrim p, PrimPatchBase p) => Non p wX -> l (PrimOf p) wX wY -> Maybe (Non p wY)
- (>>*) :: (WL l, Apply p, Commute p, Invert p, ToFromPrim p) => l (PrimOf p) wX wY -> Non p wY -> Maybe (Non p wX)
Documentation
A Non
stores a context with a Prim
patch. It is a patch whose effect
isn't visible - a Non-affecting patch.
class Nonable p where Source #
Nonable represents the class of patches that can be turned into a Non.
Instances
PrimPatch prim => Nonable (RepoPatchV2 prim) Source # | |
Defined in Darcs.Patch.V2.RepoPatch non :: RepoPatchV2 prim wX wY -> Non (RepoPatchV2 prim) wX Source # |
unNon :: FromPrim p => Non p wX -> Sealed (FL p wX) Source #
unNon converts a Non into a FL of its context followed by the primitive patch.
showNon :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => ShowPatchFor -> Non p wX -> Doc Source #
showNon creates a Doc representing a Non.
showNons :: (ShowPatchBasic p, PatchListFormat p, PrimPatchBase p) => ShowPatchFor -> [Non p wX] -> Doc Source #
showNons creates a Doc representing a list of Nons.
readNon :: (ReadPatch p, PatchListFormat p, PrimPatchBase p) => Parser (Non p wX) Source #
readNon is a parser that attempts to read a single Non.
readNons :: (ReadPatch p, PatchListFormat p, PrimPatchBase p) => Parser [Non p wX] Source #
readNons is a parser that attempts to read a list of Nons.
commutePrimsOrAddToCtx :: (WL l, Apply p, Commute p, Invert p, ToFromPrim p) => l (PrimOf p) wX wY -> Non p wY -> Non p wX Source #
commutePrimsOrAddToCtx takes a WL of prims and attempts to commute them past a Non.
commuteOrAddToCtx :: (Commute p, ToFromPrim p) => p wX wY -> Non p wY -> Non p wX Source #
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 :: (Commute p, Invert p, Eq2 p, ToFromPrim p) => p wX wY -> Non p wX -> Maybe (Non p wY) 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 :: (Apply p, Commute p, Invert p, ToFromPrim p) => RL p wX wY -> Non p wY -> Non p wX Source #
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 :: (Apply p, Commute p, Invert p, Eq2 p, ToFromPrim p) => FL p wX wY -> Non p wX -> Maybe (Non p wY) 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, Apply p, Commute p, Invert p, Eq2 p, ToFromPrim p, PrimPatchBase p) => [Non p wX] -> Non p wX -> Non p wX Source #
(*>) :: (Commute p, Invert p, ToFromPrim p) => Non p wX -> p wX wY -> Maybe (Non p wY) Source #
(*>) attemts to modify a Non by commuting it past a given patch.
(>*) :: (Commute p, ToFromPrim p) => p wX wY -> Non p wY -> Maybe (Non p wX) Source #
(>*) attempts to modify a Non, by commuting a given patch past it.