darcs-2.1.98.2: a distributed, interactive, smart revision control systemSource codeContentsIndex
Darcs.Patch.Prim
Synopsis
data Prim where
Move :: !FileName -> !FileName -> Prim
DP :: !FileName -> !DirPatchType -> Prim
FP :: !FileName -> !FilePatchType -> Prim
Split :: FL Prim -> Prim
Identity :: Prim
ChangePref :: !String -> !String -> !String -> Prim
data IsConflictedPrim where
IsC :: !ConflictState -> !Prim -> IsConflictedPrim
data ConflictState
= Okay
| Conflicted
| Duplicated
showPrim :: FileNameFormat -> Prim -> Doc
data DirPatchType
= RmDir
| AddDir
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
= Unknown
| Failed
| Succeeded a
null_patch :: Prim
nullP :: Prim -> EqCheck
is_null_patch :: Prim -> Bool
is_identity :: Prim -> EqCheck
formatFileName :: FileNameFormat -> FileName -> Doc
data FileNameFormat
= OldFormat
| NewFormat
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
is_addfile :: Prim -> Bool
is_hunk :: Prim -> Bool
is_binary :: Prim -> Bool
is_setpref :: Prim -> Bool
is_similar :: Prim -> Prim -> Bool
is_adddir :: Prim -> Bool
is_filepatch :: Prim -> Maybe FileName
canonize :: Prim -> FL Prim
try_to_shrink :: FL Prim -> FL Prim
modernizePrim :: Prim -> FL Prim
subcommutes :: [(String, CommuteFunction)]
sort_coalesceFL :: FL Prim -> FL Prim
join :: (Prim :> Prim) -> Maybe Prim
applyBinary :: ByteString -> ByteString -> FileContents -> Maybe FileContents
try_tok_internal :: String -> ByteString -> ByteString -> ByteString -> Maybe [ByteString]
try_shrinking_inverse :: FL Prim -> Maybe (FL Prim)
class FromPrim p where
fromPrim :: Prim -> p
class FromPrims p where
fromPrims :: FL Prim -> p
joinPatches :: FL p -> p
class FromPrim p => ToFromPrim p where
toPrim :: p -> Maybe Prim
class (Invert p, Commute p, Effect p) => Conflict p where
list_conflicted_files :: p -> [FilePath]
resolve_conflicts :: p -> [[Sealed (FL Prim)]]
commute_no_conflicts :: (p :> p) -> Maybe (p :> p)
conflictedEffect :: p -> [IsConflictedPrim]
class Effect p where
effect :: p -> FL Prim
effectRL :: p -> RL Prim
isHunk :: p -> Maybe Prim
commute_no_conflictsFL :: Conflict p => (p :> FL p) -> Maybe (FL p :> p)
commute_no_conflictsRL :: Conflict p => (RL p :> p) -> Maybe (p :> RL p)
Documentation
data Prim whereSource
Constructors
Move :: !FileName -> !FileName -> Prim
DP :: !FileName -> !DirPatchType -> Prim
FP :: !FileName -> !FilePatchType -> Prim
Split :: FL Prim -> Prim
Identity :: Prim
ChangePref :: !String -> !String -> !String -> Prim
show/hide Instances
data IsConflictedPrim whereSource
Constructors
IsC :: !ConflictState -> !Prim -> IsConflictedPrim
data ConflictState Source
Constructors
Okay
Conflicted
Duplicated
show/hide Instances
showPrim :: FileNameFormat -> Prim -> DocSource
data DirPatchType Source
Constructors
RmDir
AddDir
show/hide Instances
data FilePatchType Source
Constructors
RmFile
AddFile
Hunk !Int [ByteString] [ByteString]
TokReplace !String !String !String
Binary ByteString ByteString
show/hide Instances
type CommuteFunction = (Prim :< Prim) -> Perhaps (Prim :< Prim)Source
data Perhaps a Source
Constructors
Unknown
Failed
Succeeded a
show/hide Instances
null_patch :: PrimSource
nullP :: Prim -> EqCheckSource
is_null_patch :: Prim -> BoolSource
is_identity :: Prim -> EqCheckSource
formatFileName :: FileNameFormat -> FileName -> DocSource
data FileNameFormat Source
Constructors
OldFormat
NewFormat
adddir :: FilePath -> PrimSource
addfile :: FilePath -> PrimSource
binary :: FilePath -> ByteString -> ByteString -> PrimSource
changepref :: String -> String -> String -> PrimSource
hunk :: FilePath -> Int -> [ByteString] -> [ByteString] -> PrimSource
move :: FilePath -> FilePath -> PrimSource
rmdir :: FilePath -> PrimSource
rmfile :: FilePath -> PrimSource
tokreplace :: FilePath -> String -> String -> String -> PrimSource
is_addfile :: Prim -> BoolSource
is_hunk :: Prim -> BoolSource
is_binary :: Prim -> BoolSource
is_setpref :: Prim -> BoolSource
is_similar :: Prim -> Prim -> BoolSource
is_adddir :: Prim -> BoolSource
is_filepatch :: Prim -> Maybe FileNameSource
canonize :: Prim -> FL PrimSource
try_to_shrink :: FL Prim -> FL PrimSource
modernizePrim :: Prim -> FL PrimSource
subcommutes :: [(String, CommuteFunction)]Source
sort_coalesceFL :: FL Prim -> FL PrimSource
sort_coalesceFL ps coalesces as many patches in ps as possible, sorting the results according to the scheme defined in comparePrim
join :: (Prim :> Prim) -> Maybe PrimSource
applyBinary :: ByteString -> ByteString -> FileContents -> Maybe FileContentsSource
try_tok_internal :: String -> ByteString -> ByteString -> ByteString -> Maybe [ByteString]Source
try_shrinking_inverse :: FL Prim -> Maybe (FL Prim)Source
class FromPrim p whereSource
Methods
fromPrim :: Prim -> pSource
show/hide Instances
class FromPrims p whereSource
Methods
fromPrims :: FL Prim -> pSource
joinPatches :: FL p -> pSource
show/hide Instances
class FromPrim p => ToFromPrim p whereSource
Methods
toPrim :: p -> Maybe PrimSource
show/hide Instances
class (Invert p, Commute p, Effect p) => Conflict p whereSource
Methods
list_conflicted_files :: p -> [FilePath]Source
resolve_conflicts :: p -> [[Sealed (FL Prim)]]Source
commute_no_conflicts :: (p :> p) -> Maybe (p :> p)Source
conflictedEffect :: p -> [IsConflictedPrim]Source
show/hide Instances
class Effect p whereSource
Methods
effect :: p -> FL PrimSource
effectRL :: p -> RL PrimSource
isHunk :: p -> Maybe PrimSource
show/hide Instances
commute_no_conflictsFL :: Conflict p => (p :> FL p) -> Maybe (FL p :> p)Source
commute_no_conflictsRL :: Conflict p => (RL p :> p) -> Maybe (p :> RL p)Source
Produced by Haddock version 2.4.2