Safe Haskell | None |
---|---|
Language | Haskell2010 |
- restrictSubpaths :: forall rt p m wR wU wT. (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> [SubPath] -> IO (TreeFilter m)
- restrictBoring :: forall m. Tree m -> IO (TreeFilter m)
- newtype TreeFilter m = TreeFilter {
- applyTreeFilter :: forall tr. FilterTree tr m => tr m -> tr m
- restrictDarcsdir :: forall m. TreeFilter m
- maybeRestrictSubpaths :: forall rt p m wR wU wT. (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> Maybe [SubPath] -> IO (TreeFilter m)
- unrecordedChanges :: forall rt p wR wU wT. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO (FL (PrimOf p) wT wU)
- unrecordedChangesWithPatches :: forall rt p wR wU wT wX. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => FL (PrimOf p) wX wT -> FL (PrimOf p) wT wT -> (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO (FL (PrimOf p) wT wU)
- readPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO (Tree IO, Sealed (FL p wT))
- readRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO (Tree IO)
- readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> Maybe [SubPath] -> IO (Tree IO)
- readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO (Tree IO)
- readWorking :: IO (Tree IO)
- readPendingAndWorking :: forall rt p wR wU wT. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO ((FL (PrimOf p) :> FL (PrimOf p)) wT wU)
- readUnrecordedFiltered :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> UseIndex -> ScanKnown -> Maybe [SubPath] -> IO (Tree IO)
- readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO Index
- updateIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO ()
- invalidateIndex :: t -> IO ()
- data UseIndex
- data ScanKnown
- filterOutConflicts :: (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => RL (PatchInfoAnd rt p) wX wT -> Repository rt p wR wU wT -> FL (PatchInfoAnd rt p) wX wZ -> IO (Bool, Sealed (FL (PatchInfoAnd rt p) wX))
- getMovesPs :: forall rt p wR wU wB prim. (PrimConstruct prim, PrimCanonize prim, RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => Repository rt p wR wU wR -> Maybe [SubPath] -> IO (FL prim wB wB)
- getReplaces :: forall rt p wR wU wT wX. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree, wX ~ wR) => (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO (Sealed (FL (PrimOf p) wX))
Documentation
restrictSubpaths :: forall rt p m wR wU wT. (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> [SubPath] -> IO (TreeFilter m) Source #
From a repository and a list of SubPath'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 :: forall m. Tree m -> IO (TreeFilter m) Source #
Construct a Tree filter that removes any boring files the Tree might have contained. Additionally, you should (in most cases) pass an (expanded) Tree that corresponds to the recorded content of the repository. This is important in the cases when the repository contains files that would be boring otherwise. (If you pass emptyTree instead, such files will simply be discarded by the filter, which is usually not what you want.)
This function is most useful when you have a plain Tree corresponding to the full working copy of the repository, including untracked files. Cf. whatsnew, record --look-for-adds.
newtype TreeFilter m Source #
TreeFilter | |
|
restrictDarcsdir :: forall m. TreeFilter m Source #
Construct a Tree filter that removes any darcs metadata files the Tree might have contained.
maybeRestrictSubpaths :: forall rt p m wR wU wT. (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> Maybe [SubPath] -> IO (TreeFilter m) Source #
Diffs
unrecordedChanges :: forall rt p wR wU wT. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO (FL (PrimOf p) wT 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 copy + 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: with LookForAdds, we will include any non-boring files (i.e. also those that do not exist in the "recorded" state) in the working in the "unrecorded" state, and therefore they will show up in the patches as addfiles.
The IgnoreTimes option 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).
unrecordedChangesWithPatches :: forall rt p wR wU wT wX. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => FL (PrimOf p) wX wT -> FL (PrimOf p) wT wT -> (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO (FL (PrimOf p) wT wU) Source #
readPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO (Tree IO, Sealed (FL p wT)) Source #
Obtains a Tree corresponding to the recorded state of the repository and a pending patch to go with it. The pending patch should start at the recorded state (we even verify that it applies, and degrade to renaming pending and starting afresh if it doesn't), but we've set to say it starts at the tentative state.
Question (Eric Kow) Is this a bug? Darcs.Repository.Pending.readPending says it is
Trees
readRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> 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 wR wU wT -> Maybe [SubPath] -> 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.
readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO (Tree IO) Source #
Obtains the same Tree as readRecorded
would but with the additional side
effect of reading/checking the pending patch.
readWorking :: IO (Tree IO) Source #
Obtains a Tree corresponding to the complete working copy of the repository (modified and non-modified files).
readPendingAndWorking :: forall rt p wR wU wT. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO ((FL (PrimOf p) :> FL (PrimOf p)) wT wU) Source #
readUnrecordedFiltered :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> UseIndex -> ScanKnown -> Maybe [SubPath] -> IO (Tree IO) Source #
A variant of readUnrecorded
that takes the UseIndex and ScanKnown
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 wR wU wT -> IO Index Source #
updateIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> IO () Source #
invalidateIndex :: t -> IO () Source #
Mark the existing index as invalid. This has to be called whenever the listing of pristine changes and will cause darcs to update the index next time it tries to read it. (NB. This is about files added and removed from pristine: changes to file content in either pristine or working are handled transparently by the index reading code.)
ScanKnown | Just files already known to darcs |
ScanAll | All files, i.e. look for new ones |
ScanBoring | All files, even boring ones |
Utilities
:: (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) | |
=> RL (PatchInfoAnd rt p) wX wT | Recorded patches from repository, starting from same context as the patches to filter |
-> Repository rt p wR wU wT | Repository itself, used for grabbing unrecorded changes |
-> FL (PatchInfoAnd rt p) wX wZ | Patches to filter |
-> IO (Bool, Sealed (FL (PatchInfoAnd rt 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
Detection of changes
getMovesPs :: forall rt p wR wU wB prim. (PrimConstruct prim, PrimCanonize prim, RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => Repository rt p wR wU wR -> Maybe [SubPath] -> IO (FL prim wB wB) Source #
Automatically detect file moves using the index
getReplaces :: forall rt p wR wU wT wX. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree, wX ~ wR) => (UseIndex, ScanKnown, DiffAlgorithm) -> Repository rt p wR wU wT -> Maybe [SubPath] -> IO (Sealed (FL (PrimOf p) wX)) Source #
Search for possible replaces between the recordedAndPending state and the unrecorded (or working) state. Return a Sealed FL list of replace patches to be applied to the recordedAndPending state.