Safe Haskell | Safe-Infered |
---|
- selectChanges :: forall p x y. (Patchy p, ApplyState p ~ Tree) => WhichChanges -> FL p x y -> PatchSelection p x y
- data WhichChanges
- = Last
- | LastReversed
- | First
- | FirstReversed
- viewChanges :: (Patchy p, ApplyState p ~ Tree) => [DarcsFlag] -> [Sealed2 p] -> IO ()
- withSelectedPatchFromRepo :: forall p r u t. (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> [DarcsFlag] -> (forall a. (FL (PatchInfoAnd p) :> PatchInfoAnd p) a r -> IO ()) -> IO ()
- filterOutConflicts :: (RepoPatch p, ApplyState p ~ Tree) => [DarcsFlag] -> RL (PatchInfoAnd p) x t -> Repository p r u t -> FL (PatchInfoAnd p) x z -> IO (Bool, Sealed (FL (PatchInfoAnd p) x))
- runSelection :: Patchy p => PatchSelection p x y -> PatchSelectionContext p -> IO ((FL p :> FL p) x y)
- selectionContextPrim :: PrimPatch prim => String -> [DarcsFlag] -> Maybe (Splitter prim) -> Maybe [FilePath] -> Maybe (Tree IO) -> PatchSelectionContext prim
- selectionContext :: RepoPatch p => String -> [DarcsFlag] -> Maybe (Splitter (PatchInfoAnd p)) -> Maybe [FilePath] -> PatchSelectionContext (PatchInfoAnd p)
Documentation
selectChanges :: forall p x y. (Patchy p, ApplyState p ~ Tree) => WhichChanges -> FL p x y -> PatchSelection p x ySource
Select patches from a FL
.
data WhichChanges Source
When asking about patches, we either ask about them in oldest-first or newest first (with respect to the current ordering of the repository), and we either want an initial segment or a final segment of the poset of patches.
First
: ask for an initial
segment, first patches first (default for all pull-like commands)
FirstReversed
: ask for an initial segment, last patches first
(used to ask about dependencies in record, and for pull-like
commands with the --reverse
flag).
LastReversed
: ask for a final segment, last patches first. (default
for unpull-like commands, except for selecting *primitive* patches in
rollback)
Last
: ask for a final segment, first patches first. (used for selecting
primitive patches in rollback, and for unpull-like commands with the
--reverse
flag
viewChanges :: (Patchy p, ApplyState p ~ Tree) => [DarcsFlag] -> [Sealed2 p] -> IO ()Source
The equivalent of selectChanges
for the darcs changes
command
withSelectedPatchFromRepo :: forall p r u t. (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> [DarcsFlag] -> (forall a. (FL (PatchInfoAnd p) :> PatchInfoAnd p) a r -> IO ()) -> IO ()Source
The function for selecting a patch to amend record. Read at your own risks.
:: (RepoPatch p, ApplyState p ~ Tree) | |
=> [DarcsFlag] | Command-line options. Only |
-> RL (PatchInfoAnd p) x t | Recorded patches from repository, starting from same context as the patches to filter |
-> Repository p r u t | Repository itself, used for grabbing unrecorded changes |
-> FL (PatchInfoAnd p) x z | Patches to filter |
-> IO (Bool, Sealed (FL (PatchInfoAnd p) x)) | (True iff any patches were removed, possibly filtered patches) |
Optionally remove any patches (+dependencies) from a sequence that conflict with the recorded or unrecorded changes in a repo
runSelection :: Patchy p => PatchSelection p x y -> PatchSelectionContext p -> IO ((FL p :> FL p) x y)Source
runs a PatchSelection
action in the given PatchSelectionContext
.
selectionContextPrim :: PrimPatch prim => String -> [DarcsFlag] -> Maybe (Splitter prim) -> Maybe [FilePath] -> Maybe (Tree IO) -> PatchSelectionContext primSource
A PatchSelectionContext
for selecting Prim
patches.
selectionContext :: RepoPatch p => String -> [DarcsFlag] -> Maybe (Splitter (PatchInfoAnd p)) -> Maybe [FilePath] -> PatchSelectionContext (PatchInfoAnd p)Source
A PatchSelectionContext
for selecting full patches (PatchInfoAnd
patches)