- data Prim where
- data IsConflictedPrim where
- IsC :: !ConflictState -> !Prim -> IsConflictedPrim
- data ConflictState
- = Okay
- | Conflicted
- | Duplicated
- showPrim :: FileNameFormat -> Prim -> Doc
- showPrimFL :: FileNameFormat -> FL Prim -> Doc
- showHunk :: FileNameFormat -> FileName -> Int -> [ByteString] -> [ByteString] -> Doc
- data DirPatchType
- data FilePatchType
- = RmFile
- | AddFile
- | Hunk !Int [ByteString] [ByteString]
- | TokReplace !String !String !String
- | Binary ByteString ByteString
- type CommuteFunction = (Prim :< Prim) -> Perhaps (Prim :< Prim)
- data Perhaps a
- null_patch :: Prim
- nullP :: Prim -> EqCheck
- isNullPatch :: Prim -> Bool
- isIdentity :: Prim -> EqCheck
- formatFileName :: FileNameFormat -> FileName -> Doc
- data FileNameFormat
- adddir :: FilePath -> Prim
- addfile :: FilePath -> Prim
- binary :: FilePath -> ByteString -> ByteString -> Prim
- changepref :: String -> String -> String -> Prim
- hunk :: FilePath -> Int -> [ByteString] -> [ByteString] -> Prim
- move :: FilePath -> FilePath -> Prim
- rmdir :: FilePath -> Prim
- rmfile :: FilePath -> Prim
- tokreplace :: FilePath -> String -> String -> String -> Prim
- primIsAddfile :: Prim -> Bool
- primIsHunk :: Prim -> Bool
- primIsBinary :: Prim -> Bool
- primIsSetpref :: Prim -> Bool
- isSimilar :: Prim -> Prim -> Bool
- primIsAdddir :: Prim -> Bool
- is_filepatch :: Prim -> Maybe FileName
- canonize :: Prim -> FL Prim
- tryToShrink :: FL Prim -> FL Prim
- modernizePrim :: Prim -> FL Prim
- subcommutes :: [(String, (Prim :< Prim) -> Perhaps (Prim :< Prim))]
- sortCoalesceFL :: FL Prim -> FL Prim
- join :: (Prim :> Prim) -> Maybe Prim
- canonizeFL :: FL Prim -> FL Prim
- tryTokInternal :: String -> ByteString -> ByteString -> ByteString -> Maybe [ByteString]
- tryShrinkingInverse :: FL Prim -> Maybe (FL Prim)
- nFn :: FilePath -> FilePath
- class FromPrim p where
- class FromPrims p where
- fromPrims :: FL Prim -> p
- joinPatches :: FL p -> p
- class FromPrim p => ToFromPrim p where
- class (Invert p, Commute p, Effect p) => Conflict p where
- listConflictedFiles :: p -> [FilePath]
- resolveConflicts :: p -> [[Sealed (FL Prim)]]
- commuteNoConflicts :: (p :> p) -> Maybe (p :> p)
- conflictedEffect :: p -> [IsConflictedPrim]
- isInconsistent :: p -> Maybe Doc
- class Effect p where
- commuteNoConflictsFL :: Conflict p => (p :> FL p) -> Maybe (FL p :> p)
- commuteNoConflictsRL :: Conflict p => (RL p :> p) -> Maybe (p :> RL p)
Documentation
data IsConflictedPrim whereSource
IsC :: !ConflictState -> !Prim -> IsConflictedPrim |
data ConflictState Source
showPrim :: FileNameFormat -> Prim -> DocSource
showPrimFL :: FileNameFormat -> FL Prim -> DocSource
showHunk :: FileNameFormat -> FileName -> Int -> [ByteString] -> [ByteString] -> DocSource
data DirPatchType Source
data FilePatchType Source
isNullPatch :: Prim -> BoolSource
isIdentity :: Prim -> EqCheckSource
formatFileName :: FileNameFormat -> FileName -> DocSource
binary :: FilePath -> ByteString -> ByteString -> PrimSource
hunk :: FilePath -> Int -> [ByteString] -> [ByteString] -> PrimSource
primIsAddfile :: Prim -> BoolSource
primIsHunk :: Prim -> BoolSource
primIsBinary :: Prim -> BoolSource
primIsSetpref :: Prim -> BoolSource
isSimilar :: Prim -> Prim -> BoolSource
Tells you if two patches are in the same category, human-wise. Currently just returns true if they are filepatches on the same file.
primIsAdddir :: Prim -> BoolSource
is_filepatch :: Prim -> Maybe FileNameSource
modernizePrim :: Prim -> FL PrimSource
sortCoalesceFL :: FL Prim -> FL PrimSource
sortCoalesceFL
ps
coalesces as many patches in ps
as
possible, sorting the results according to the scheme defined
in comparePrim
canonizeFL :: FL Prim -> FL PrimSource
canonizeFL
ps
puts a sequence of primitive patches into
canonical form. Even if the patches are just hunk patches,
this is not necessarily the same set of results as you would get
if you applied the sequence to a specific tree and recalculated
a diff.
Note that this process does not preserve the commutation behaviour of the patches and is therefore not appropriate for use when working with already recorded patches (unless doing amend-record or the like).
tryTokInternal :: String -> ByteString -> ByteString -> ByteString -> Maybe [ByteString]Source
class FromPrim p => ToFromPrim p whereSource
class (Invert p, Commute p, Effect p) => Conflict p whereSource
listConflictedFiles :: p -> [FilePath]Source
resolveConflicts :: p -> [[Sealed (FL Prim)]]Source
commuteNoConflicts :: (p :> p) -> Maybe (p :> p)Source
If commuteNoConflicts
x :> y
succeeds, we know that that x
commutes
past y
without any conflicts. This function is useful for patch types
for which commute
is defined to always succeed; so we need some way to
pick out the specific cases where commutation succeeds without any conflicts.
Consider the commute square with patch names written in capital letters and repository states written in small letters.
X o-->--a | | Y' v v Y | | z-->--b X'
The default definition of this function checks that we can mirror the commutation with patch inverses (written with the negative sign)
-X X a-->--o-->--a | | | Y'' v Y' v v Y | | | b-->--z-->--b (-X)' X'
We check that commuting X
and Y
succeeds, as does commuting -X
and Y'
.
It also checks that Y'' == Y
and that -(X')
is the same as (-X)'
conflictedEffect :: p -> [IsConflictedPrim]Source
isInconsistent :: p -> Maybe DocSource
Patches whose concrete effect which can be expressed as a list of primitive patches.
A minimal definition would be either of effect
or effectRL
.