| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Darcs.Patch.V3.Contexted
Description
Contexted patches.
Synopsis
- data Contexted p wX
 - ctxId :: Ident p => Contexted p wX -> PatchId p
 - ctxView :: Contexted p wX -> Sealed ((FL p :> p) wX)
 - ctxNoConflict :: (CleanMerge p, Commute p, Ident p) => Contexted p wX -> Contexted p wX -> Bool
 - ctxToFL :: Contexted p wX -> Sealed (FL p wX)
 - ctx :: p wX wY -> Contexted p wX
 - ctxAdd :: (Commute p, Invert p, Ident p) => p wX wY -> Contexted p wY -> Contexted p wX
 - ctxAddRL :: (Commute p, Invert p, Ident p) => RL p wX wY -> Contexted p wY -> Contexted p wX
 - ctxAddInvFL :: (Commute p, Invert p, Ident p) => FL p wX wY -> Contexted p wX -> Contexted p wY
 - ctxAddFL :: (Commute p, Invert p, Ident p) => FL p wX wY -> Contexted p wY -> Contexted p wX
 - commutePast :: Commute p => p wX wY -> Contexted p wY -> Maybe (Contexted p wX)
 - commutePastRL :: Commute p => RL p wX wY -> Contexted p wY -> Maybe (Contexted p wX)
 - ctxTouches :: PatchInspect p => Contexted p wX -> [AnchoredPath]
 - ctxHunkMatches :: PatchInspect p => (ByteString -> Bool) -> Contexted p wX -> Bool
 - showCtx :: (ShowPatchBasic p, PatchListFormat p) => ShowPatchFor -> Contexted p wX -> Doc
 - readCtx :: (ReadPatch p, PatchListFormat p) => Parser (Contexted p wX)
 - prop_ctxInvariants :: (Commute p, Invert p, SignedIdent p) => Contexted p wX -> Bool
 - prop_ctxEq :: (Commute p, Eq2 p, Ident p) => Contexted p wX -> Contexted p wX -> Bool
 - prop_ctxPositive :: SignedIdent p => Contexted p wX -> Bool
 
Contexted patches
Instances
| Show2 p => Show1 (Contexted p) Source # | |
| Ident p => Eq (Contexted p wX) Source # | Equality between   | 
| Ident p => Ord (Contexted p wX) Source # | |
Defined in Darcs.Patch.V3.Contexted Methods compare :: Contexted p wX -> Contexted p wX -> Ordering # (<) :: Contexted p wX -> Contexted p wX -> Bool # (<=) :: Contexted p wX -> Contexted p wX -> Bool # (>) :: Contexted p wX -> Contexted p wX -> Bool # (>=) :: Contexted p wX -> Contexted p wX -> Bool #  | |
| Show2 p => Show (Contexted p wX) Source # | |
Query
ctxNoConflict :: (CleanMerge p, Commute p, Ident p) => Contexted p wX -> Contexted p wX -> Bool Source #
Contexted patches conflict with each other if the identity of one is in
 the context of the other or they cannot be merged cleanly.
Construct
ctxAdd :: (Commute p, Invert p, Ident p) => p wX wY -> Contexted p wY -> Contexted p wX Source #
Add a patch to the context of a Contexted patch. This is
 the place where we take care of the invariants.
ctxAddRL :: (Commute p, Invert p, Ident p) => RL p wX wY -> Contexted p wY -> Contexted p wX Source #
Add an RL of patches to the context.
ctxAddInvFL :: (Commute p, Invert p, Ident p) => FL p wX wY -> Contexted p wX -> Contexted p wY Source #
Add an FL of patches to the context but invert it first.
ctxAddFL :: (Commute p, Invert p, Ident p) => FL p wX wY -> Contexted p wY -> Contexted p wX Source #
Add an FL of patches to the context.
commutePastRL :: Commute p => RL p wX wY -> Contexted p wY -> Maybe (Contexted p wX) Source #
Not defined in the paper but used in the commute algorithm.
PatchInspect helpers
ctxTouches :: PatchInspect p => Contexted p wX -> [AnchoredPath] Source #
ctxHunkMatches :: PatchInspect p => (ByteString -> Bool) -> Contexted p wX -> Bool Source #
ReadPatch and ShowPatch helpers
showCtx :: (ShowPatchBasic p, PatchListFormat p) => ShowPatchFor -> Contexted p wX -> Doc Source #
Properties
prop_ctxInvariants :: (Commute p, Invert p, SignedIdent p) => Contexted p wX -> Bool Source #
This property states that no prefix of the context commutes with the rest
 of the Contexted patch and that the context never contains a patch
 and its inverse.
prop_ctxPositive :: SignedIdent p => Contexted p wX -> Bool Source #