|
|
|
|
| Synopsis |
|
| class (Patchy p, Effect p, FromPrims p, Conflict p) => RepoPatch p | | | data Prim | | | data Patch | | | data RealPatch | | | data Named p | | | class (Apply p, Commute p, ShowPatch p, ReadPatch p, Invert p) => Patchy p | | | flattenFL :: Patch -> FL Patch | | | joinPatches :: FromPrims p => FL p -> p | | | fromPrim :: FromPrim p => Prim -> p | | | fromPrims :: FromPrims p => FL Prim -> p | | | is_null_patch :: Patch -> Bool | | | nullP :: Patch -> EqCheck | | | rmfile :: FilePath -> Prim | | | addfile :: FilePath -> Prim | | | rmdir :: FilePath -> Prim | | | adddir :: FilePath -> Prim | | | move :: FilePath -> FilePath -> Prim | | | hunk :: FilePath -> Int -> [ByteString] -> [ByteString] -> Prim | | | tokreplace :: FilePath -> String -> String -> String -> Prim | | | namepatch :: Patchy p => String -> String -> String -> [String] -> p -> IO (Named p) | | | anonymous :: Patchy p => p -> IO (Named p) | | | binary :: FilePath -> ByteString -> ByteString -> Prim | | | description :: ShowPatch p => p -> Doc | | | showContextPatch :: ShowPatch p => Slurpy -> p -> Doc | | | showPatch :: ShowPatch p => p -> Doc | | | showNicely :: ShowPatch p => p -> Doc | | | infopatch :: Patchy p => PatchInfo -> p -> Named p | | | changepref :: String -> String -> String -> Prim | | | thing :: ShowPatch p => p -> String | | | things :: ShowPatch p => p -> String | | | is_similar :: Prim -> Prim -> Bool | | | is_addfile :: Prim -> Bool | | | is_hunk :: Prim -> Bool | | | is_setpref :: Prim -> Bool | | | merger :: String -> Patch -> Patch -> Patch | | | is_merger :: Patch -> Bool | | | merge :: Commute p => (p :\/: p) -> p :/\: p | | | commute :: Commute p => (p :> p) -> Maybe (p :> p) | | | commutex :: Commute p => (p :< p) -> Maybe (p :< p) | | | list_touched_files :: Commute p => p -> [FilePath] | | | unravel :: Patch -> [FL Prim] | | | elegant_merge :: (Patch :\/: Patch) -> Maybe (Patch :/\: Patch) | | | resolve_conflicts :: Conflict p => p -> [[Sealed (FL Prim)]] | | | class Effect p where | | | | is_binary :: Prim -> Bool | | | gzWritePatch :: ShowPatch p => FilePath -> p -> IO () | | | writePatch :: ShowPatch p => FilePath -> p -> IO () | | | is_adddir :: Prim -> Bool | | | invert :: Invert p => p -> p | | | invertFL :: Invert p => FL p -> RL p | | | invertRL :: Invert p => RL p -> FL p | | | identity :: Invert p => p | | | commuteFL :: Commute p => (p :> FL p) -> Either (Sealed2 p) (FL p :> p) | | | commuteRL :: Commute p => (RL p :> p) -> Maybe (p :> RL p) | | | readPatch :: ReadPatch p => ByteString -> Maybe (Sealed p, ByteString) | | | canonize :: Prim -> FL Prim | | | sort_coalesceFL :: FL Prim -> FL Prim | | | try_to_shrink :: FL Prim -> FL Prim | | | apply_to_slurpy :: (Apply p, Monad m) => p -> Slurpy -> m Slurpy | | | patchname :: Named p -> String | | | patchcontents :: Named p -> p | | | apply_to_filepaths :: Apply p => p -> [FilePath] -> [FilePath] | | | force_replace_slurpy :: Prim -> Slurpy -> Maybe Slurpy | | | apply :: (Apply p, WriteableDirectory m) => [DarcsFlag] -> p -> m () | | | patch2patchinfo :: Named p -> PatchInfo | | | | | type MarkedUpFile = [(ByteString, LineMark)] | | | markup_file :: Effect p => PatchInfo -> p -> (FilePath, MarkedUpFile) -> (FilePath, MarkedUpFile) | | | empty_markedup_file :: MarkedUpFile | | | summary :: ShowPatch p => p -> Doc | | | summarize :: (Conflict e, Effect e) => e -> Doc | | | xml_summary :: (Effect p, Patchy p, Conflict p) => Named p -> Doc | | | adddeps :: Named p -> [PatchInfo] -> Named p | | | getdeps :: Named p -> [PatchInfo] | | | list_conflicted_files :: Conflict p => p -> [FilePath] | | | modernize_patch :: Patch -> Patch | | | | | patchChanges :: Prim -> [(String, DirMark)] | | | applyToPop :: PatchInfo -> FL Prim -> Population -> Population |
|
|
| Documentation |
|
|
| Instances | |
|
|
|
Instances | |
|
|
|
Instances | |
|
|
|
Duplicate x: This patch has no effect since x is already present in the repository
Etacilpud x: invert (Duplicate x) Normal prim: A primitive patch
Conflictor ix xx x:
ix is the set of patches:
- that conflict with x and also conflict with another patch in the repository
- that conflict with a patch that conflict with x
xx is the sequence of patches that conflict *only* with x
x is the current patch
ix and x are stored as Non objects, which include any necessary
context to uniquely define the patch that is referred to.
InvConflictor ix xx x: like invert (Conflictor ix xx x)
| Instances | |
|
|
|
Instances | |
|
|
|
| Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| | Methods | | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| sort_coalesceFL ps coalesces as many patches in ps as
possible, sorting the results according to the scheme defined
in comparePrim
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Constructors | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| info of a directory member
| | Constructors | | AddedFile | | | RemovedFile | | | MovedFile String | | | ModifiedFile | | | DullFile | | | AddedDir | | | RemovedDir | | | MovedDir !String | | | DullDir | |
| Instances | |
|
|
|
|
|
|
| Produced by Haddock version 2.4.2 |