Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- restrictSubpaths :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> [AnchoredPath] -> IO (TreeFilter m)
- restrictBoring :: Tree m -> IO (TreeFilter m)
- newtype TreeFilter m = TreeFilter {
- applyTreeFilter :: forall tr. FilterTree tr m => tr m -> tr m
- restrictDarcsdir :: TreeFilter m
- unrecordedChanges :: (RepoPatch p, ApplyState p ~ Tree) => DiffOpts -> Repository rt p wU wR -> Maybe [AnchoredPath] -> IO (FL (PrimOf p) wR wU)
- readPristine :: Repository rt p wU wR -> IO (Tree IO)
- readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> UseIndex -> Maybe [AnchoredPath] -> IO (Tree IO)
- readPristineAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> IO (Tree IO)
- readWorking :: TreeFilter IO -> IO (Tree IO)
- readPendingAndWorking :: (RepoPatch p, ApplyState p ~ Tree) => DiffOpts -> Repository rt p wU wR -> Maybe [AnchoredPath] -> IO ((FL (PrimOf p) :> FL (PrimOf p)) wR wU)
- readUnrecordedFiltered :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> UseIndex -> LookForAdds -> LookForMoves -> Maybe [AnchoredPath] -> IO (Tree IO)
- readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> IO Index
- updateIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> IO ()
- filterOutConflicts :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> UseIndex -> FL (PatchInfoAnd p) wX wR -> FL (PatchInfoAnd p) wX wZ -> IO (Bool, Sealed (FL (PatchInfoAnd p) wX))
- unsafeAddToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> FreeLeft (FL (PrimOf p)) -> IO ()
- addToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> DiffOpts -> FL (PrimOf p) wU wY -> IO ()
Documentation
restrictSubpaths :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> [AnchoredPath] -> IO (TreeFilter m) Source #
From a repository and a list of AnchoredPath's, construct a filter that can be used on a Tree (recorded or unrecorded state) of this repository. This constructed filter will take pending into account, so the subpaths will be translated correctly relative to pending move patches.
restrictBoring :: Tree m -> IO (TreeFilter m) Source #
Construct a TreeFilter
that removes any boring files that are not also
contained in the argument Tree
.
The standard use case is for the argument to be the recorded state, possibly with further patches applied, so as not to discard any files already known to darcs. The result is usually applied to the full working state.
newtype TreeFilter m Source #
TreeFilter | |
|
restrictDarcsdir :: TreeFilter m Source #
Construct a Tree filter that removes any darcs metadata files the Tree might have contained.
Diffs
unrecordedChanges :: (RepoPatch p, ApplyState p ~ Tree) => DiffOpts -> Repository rt p wU wR -> Maybe [AnchoredPath] -> IO (FL (PrimOf p) wR wU) Source #
For a repository and an optional list of paths (when Nothing
, take
everything) compute a (forward) list of prims (i.e. a patch) going from the
recorded state of the repository (pristine) to the unrecorded state of the
repository (the working tree + pending). When a list of paths is given, at
least the files that live under any of these paths in either recorded or
unrecorded will be included in the resulting patch. NB. More patches may be
included in this list, eg. the full contents of the pending patch. This is
usually not a problem, since selectChanges will properly filter the results
anyway.
This also depends on the options given:
- -look-for-moves: Detect pending file moves using the index. The resulting patches are added to pending and taken into consideration, when filtering the tree according to the given path list.
- -look-for-adds: Include files in the working state that do not exist in the recorded + pending state.
- -include-boring: Include even boring files.
- -look-for-replaces: Detect pending replace patches. Like detected moves, these are added to the pending patch. Note that, like detected moves, these are mere proposals for the user to consider or reject.
- -ignore-times: Disables index usage completely -- for each file, we read both the unrecorded and the recorded copy and run a diff on them. This is very inefficient, although in extremely rare cases, the index could go out of sync (file is modified, index is updated and file is modified again within a single second).
Note that use of the index is also disabled when we detect moves or replaces, since this implies that the index is out of date.
Trees
readPristine :: Repository rt p wU wR -> IO (Tree IO) Source #
Obtains a Tree corresponding to the "recorded" state of the repository: this is the same as the pristine cache, which is the same as the result of applying all the repository's patches to an empty directory.
readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> UseIndex -> Maybe [AnchoredPath] -> IO (Tree IO) Source #
Obtains a Tree corresponding to the "unrecorded" state of the repository: the modified files of the working tree plus the "pending" patch. The optional list of paths allows to restrict the query to a subtree.
Limiting the query may be more efficient, since hashes on the uninteresting parts of the index do not need to go through an up-to-date check (which involves a relatively expensive lstat(2) per file.
readPristineAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> IO (Tree IO) Source #
Obtains the recorded Tree
with the pending patch applied.
readWorking :: TreeFilter IO -> IO (Tree IO) Source #
Obtains the relevant (according to the given filter) part of the working tree.
readPendingAndWorking :: (RepoPatch p, ApplyState p ~ Tree) => DiffOpts -> Repository rt p wU wR -> Maybe [AnchoredPath] -> IO ((FL (PrimOf p) :> FL (PrimOf p)) wR wU) Source #
readUnrecordedFiltered :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> UseIndex -> LookForAdds -> LookForMoves -> Maybe [AnchoredPath] -> IO (Tree IO) Source #
A variant of readUnrecorded
that takes the UseIndex and LookForAdds
options into account, similar to readPendingAndWorking
. We are only
interested in the resulting tree, not the patch, so the DiffAlgorithm
option
is irrelevant.
Index
readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> IO Index Source #
Open the index or re-create it in case it is invalid or non-existing.
updateIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> IO () Source #
Update the index so that it matches pristine+pending. If the index does not exist or is invalid, create a new one.
This has to be called whenever the listing of pristine+pending changes. Note that this only concerns files added and removed or renamed: changes to file content in either pristine or working are handled transparently by the index reading code.
Utilities
:: (RepoPatch p, ApplyState p ~ Tree) | |
=> Repository rt p wU wR | Repository itself, used for grabbing unrecorded changes |
-> UseIndex | Whether to use the index when reading the working state |
-> FL (PatchInfoAnd p) wX wR | Recorded patches from repository, starting from same context as the patches to filter |
-> FL (PatchInfoAnd p) wX wZ | Patches to filter |
-> IO (Bool, Sealed (FL (PatchInfoAnd p) wX)) | True iff any patches were removed, possibly filtered patches |
Remove any patches (+dependencies) from a sequence that conflict with the recorded or unrecorded changes in a repo
Pending-related functions that depend on repo state
unsafeAddToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> FreeLeft (FL (PrimOf p)) -> IO () Source #
Add an FL
of patches started from the pending state to the pending patch.
addToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> DiffOpts -> FL (PrimOf p) wU wY -> IO () Source #
Add an FL
of patches starting from the working state to the pending patch,
including as much extra context as is necessary (context meaning
dependencies), by commuting the patches to be added past as much of the
changes between pending and working as is possible, and including anything
that doesn't commute, and the patch itself in the new pending patch.