Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Repository (rt :: RepoType) (p :: * -> * -> *) wRecordedstate wUnrecordedstate wTentativestate
- repoLocation :: Repository rt p wR wU wT -> String
- repoFormat :: Repository rt p wR wU wT -> RepoFormat
- repoPristineType :: Repository rt p wR wU wT -> PristineType
- repoCache :: Repository rt p wR wU wT -> Cache
- data PristineType
- data HashedDir
- data Cache
- data CacheLoc = Cache {}
- data CacheType
- data WritableOrNot
- cacheEntries :: Cache -> [CacheLoc]
- mkCache :: [CacheLoc] -> Cache
- reportBadSources :: IO ()
- data RepoJob a
- = RepoJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a)
- | V1Job (forall wR wU. Repository ('RepoType 'NoRebase) (RepoPatchV1 Prim) wR wU wR -> IO a)
- | V2Job (forall rt wR wU. IsRepoType rt => Repository rt (RepoPatchV2 Prim) wR wU wR -> IO a)
- | PrimV1Job (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree, IsPrimV1 (PrimOf p)) => Repository rt p wR wU wR -> IO a)
- | RebaseAwareJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a)
- | RebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a)
- | OldRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a)
- | StartRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a)
- maybeIdentifyRepository :: UseCache -> String -> IO (IdentifyRepo rt p wR wU wT)
- identifyRepositoryFor :: ReadingOrWriting -> Repository rt p wR wU wT -> UseCache -> String -> IO (Repository rt p vR vU vT)
- data ReadingOrWriting
- withRecorded :: Repository rt p wR wU wT -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a
- withRepoLock :: DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob a -> IO a
- withRepoLockCanFail :: UseCache -> RepoJob () -> IO ()
- withRepository :: UseCache -> RepoJob a -> IO a
- withRepositoryLocation :: UseCache -> String -> RepoJob a -> IO a
- withUMaskFlag :: UMask -> IO a -> IO a
- findRepository :: WorkRepo -> IO (Either String ())
- amInRepository :: WorkRepo -> IO (Either String ())
- amNotInRepository :: WorkRepo -> IO (Either String ())
- amInHashedRepository :: WorkRepo -> IO (Either String ())
- replacePristine :: Repository rt p wR wU wT -> Tree IO -> IO ()
- readRepo :: (IsRepoType rt, RepoPatch p) => Repository rt p wR wU wT -> IO (PatchSet rt p Origin wR)
- prefsUrl :: FilePath -> String
- addToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> UseIndex -> FL (PrimOf p) wU wY -> IO ()
- addPendingDiffToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> FreeLeft (FL (PrimOf p)) -> IO ()
- tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> Compression -> Verbosity -> UpdatePending -> PatchInfoAnd rt p wT wY -> IO (Repository rt p wR wU wY)
- tentativelyRemovePatches :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> Compression -> UpdatePending -> FL (PatchInfoAnd rt p) wX wT -> IO (Repository rt p wR wU wX)
- tentativelyAddToPending :: forall rt p wR wU wT wX wY. RepoPatch p => Repository rt p wR wU wT -> FL (PrimOf p) wX wY -> IO ()
- readTentativeRepo :: (IsRepoType rt, PatchListFormat p, ReadPatch p) => Repository rt p wR wU wT -> String -> IO (PatchSet rt p Origin wT)
- withManualRebaseUpdate :: forall rt p x wR wU wT1 wT2. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT1 -> (Repository rt p wR wU wT1 -> IO (Repository rt p wR wU wT2, FL (RebaseFixup (PrimOf p)) wT2 wT1, x)) -> IO (Repository rt p wR wU wT2, x)
- tentativelyMergePatches :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> String -> AllowConflicts -> ExternalMerge -> WantGuiPause -> Compression -> Verbosity -> Reorder -> (UseIndex, ScanKnown, DiffAlgorithm) -> Fork (PatchSet rt p) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) Origin wR wY -> IO (Sealed (FL (PrimOf p) wU))
- considerMergeToWorking :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> String -> AllowConflicts -> ExternalMerge -> WantGuiPause -> Compression -> Verbosity -> Reorder -> (UseIndex, ScanKnown, DiffAlgorithm) -> Fork (PatchSet rt p) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) Origin wR wY -> IO (Sealed (FL (PrimOf p) wU))
- revertRepositoryChanges :: RepoPatch p => Repository rt p wR wU wT -> UpdatePending -> IO (Repository rt p wR wU wR)
- finalizeRepositoryChanges :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> UpdatePending -> Compression -> IO (Repository rt p wT wU wT)
- createRepository :: PatchFormat -> WithWorkingDir -> WithPatchIndex -> UseCache -> IO EmptyRepository
- createRepositoryV1 :: WithWorkingDir -> WithPatchIndex -> UseCache -> IO (Repository ('RepoType 'NoRebase) (RepoPatchV1 Prim) Origin Origin Origin)
- createRepositoryV2 :: WithWorkingDir -> WithPatchIndex -> UseCache -> IO (Repository ('RepoType 'NoRebase) (RepoPatchV2 Prim) Origin Origin Origin)
- data EmptyRepository where
- EmptyRepository :: (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'NoRebase) p Origin Origin Origin -> EmptyRepository
- cloneRepository :: String -> String -> Verbosity -> UseCache -> CloneKind -> UMask -> RemoteDarcs -> SetScriptsExecutable -> RemoteRepos -> SetDefault -> InheritDefault -> [MatchFlag] -> RepoFormat -> WithWorkingDir -> WithPatchIndex -> Bool -> ForgetParent -> IO ()
- applyToWorking :: (ApplyState p ~ Tree, RepoPatch p) => Repository rt p wR wU wT -> Verbosity -> FL (PrimOf p) wU wY -> IO (Repository rt p wR wY wT)
- createPristineDirectoryTree :: Repository rt p wR wU wT -> FilePath -> WithWorkingDir -> IO ()
- createPartialsPristineDirectoryTree :: Repository rt p wR wU wT -> [AnchoredPath] -> FilePath -> IO ()
- reorderInventory :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> Compression -> IO ()
- cleanRepository :: Repository rt p wR wU wT -> IO ()
- data PatchSet rt p wStart wY
- type SealedPatchSet rt p wStart = Sealed (PatchSet rt p wStart)
- type PatchInfoAnd rt p = PatchInfoAndG rt (Named p)
- setScriptsExecutable :: IO ()
- setScriptsExecutablePatches :: PatchInspect p => p wX wY -> IO ()
- testTentative :: Repository rt p wR wU wT -> RunTest -> LeaveTestDir -> SetScriptsExecutable -> Verbosity -> IO ExitCode
- modifyCache :: (Cache -> Cache) -> Repository rt p wR wU wT -> Repository rt p wR wU wT
- readRecorded :: Repository rt p wR wU wT -> IO (Tree IO)
- readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> UseIndex -> Maybe [AnchoredPath] -> IO (Tree IO)
- unrecordedChanges :: (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> LookForMoves -> LookForReplaces -> Repository rt p wR wU wR -> Maybe [AnchoredPath] -> IO (FL (PrimOf p) wR wU)
- readPendingAndWorking :: (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> LookForMoves -> LookForReplaces -> Repository rt p wR wU wR -> Maybe [AnchoredPath] -> IO ((FL (PrimOf p) :> FL (PrimOf p)) wR wU)
- filterOutConflicts :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> FL (PatchInfoAnd rt p) wX wR -> FL (PatchInfoAnd rt p) wX wZ -> IO (Bool, Sealed (FL (PatchInfoAnd rt p) wX))
- readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO (Tree IO)
- readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO Index
- invalidateIndex :: t -> IO ()
Documentation
data Repository (rt :: RepoType) (p :: * -> * -> *) wRecordedstate wUnrecordedstate wTentativestate Source #
A Repository
is a token representing the state of a repository on disk.
It is parameterized by the patch type in the repository, and witnesses for
the recorded state of the repository (i.e. what darcs get would retrieve),
the unrecorded state (what's in the working tree now),
and the tentative state, which represents work in progress that will
eventually become the new recorded state unless something goes wrong.
Instances
Show (Repository rt p wRecordedstate wUnrecordedstate wTentativestate) Source # | |
Defined in Darcs.Repository.InternalTypes showsPrec :: Int -> Repository rt p wRecordedstate wUnrecordedstate wTentativestate -> ShowS # show :: Repository rt p wRecordedstate wUnrecordedstate wTentativestate -> String # showList :: [Repository rt p wRecordedstate wUnrecordedstate wTentativestate] -> ShowS # |
repoLocation :: Repository rt p wR wU wT -> String Source #
repoFormat :: Repository rt p wR wU wT -> RepoFormat Source #
repoPristineType :: Repository rt p wR wU wT -> PristineType Source #
repoCache :: Repository rt p wR wU wT -> Cache Source #
data PristineType Source #
Instances
Eq PristineType Source # | |
Defined in Darcs.Repository.InternalTypes (==) :: PristineType -> PristineType -> Bool # (/=) :: PristineType -> PristineType -> Bool # | |
Show PristineType Source # | |
Defined in Darcs.Repository.InternalTypes showsPrec :: Int -> PristineType -> ShowS # show :: PristineType -> String # showList :: [PristineType] -> ShowS # |
Cache is an abstract type for hiding the underlying cache locations
Cache | |
|
Instances
data WritableOrNot Source #
Instances
Eq WritableOrNot Source # | |
Defined in Darcs.Repository.Cache (==) :: WritableOrNot -> WritableOrNot -> Bool # (/=) :: WritableOrNot -> WritableOrNot -> Bool # | |
Show WritableOrNot Source # | |
Defined in Darcs.Repository.Cache showsPrec :: Int -> WritableOrNot -> ShowS # show :: WritableOrNot -> String # showList :: [WritableOrNot] -> ShowS # |
cacheEntries :: Cache -> [CacheLoc] Source #
reportBadSources :: IO () Source #
Prints an error message with a list of bad caches.
A RepoJob
wraps up an action to be performed with a repository. Because repositories
can contain different types of patches, such actions typically need to be polymorphic
in the kind of patch they work on. RepoJob
is used to wrap up the polymorphism,
and the various functions that act on a RepoJob
are responsible for instantiating
the underlying action with the appropriate patch type.
RepoJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a) | The most common |
V1Job (forall wR wU. Repository ('RepoType 'NoRebase) (RepoPatchV1 Prim) wR wU wR -> IO a) | A job that only works on darcs 1 patches |
V2Job (forall rt wR wU. IsRepoType rt => Repository rt (RepoPatchV2 Prim) wR wU wR -> IO a) | A job that only works on darcs 2 patches |
PrimV1Job (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree, IsPrimV1 (PrimOf p)) => Repository rt p wR wU wR -> IO a) | A job that works on any repository where the patch type This was added to support darcsden, which inspects the internals of V1 prim patches. In future this should be replaced with a more abstract inspection API as part of |
RebaseAwareJob (forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO a) | |
RebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a) | |
OldRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a) | |
StartRebaseJob (forall p wR wU. (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'IsRebase) p wR wU wR -> IO a) |
maybeIdentifyRepository :: UseCache -> String -> IO (IdentifyRepo rt p wR wU wT) Source #
Tries to identify the repository in a given directory
identifyRepositoryFor :: ReadingOrWriting -> Repository rt p wR wU wT -> UseCache -> String -> IO (Repository rt p vR vU vT) Source #
identifyRepositoryFor repo url
identifies (and returns) the repo at url
,
but fails if it is not compatible for reading from and writing to.
withRecorded :: Repository rt p wR wU wT -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a Source #
withRepoLock :: DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob a -> IO a Source #
Apply a given RepoJob to a repository in the current working directory. However, before doing the job, take the repo lock and initializes a repo transaction, unless this is a dry-run.
withRepoLockCanFail :: UseCache -> RepoJob () -> IO () Source #
Apply a given RepoJob to a repository in the current working directory, taking a lock. If lock not takeable, do nothing. If old-fashioned repository, do nothing. The job must not touch pending or pending.tentative, because there is no call to revertRepositoryChanges. This entry point is currently only used for attemptCreatePatchIndex.
withRepository :: UseCache -> RepoJob a -> IO a Source #
apply a given RepoJob to a repository in the current working directory
withRepositoryLocation :: UseCache -> String -> RepoJob a -> IO a Source #
apply a given RepoJob to a repository in a given url
replacePristine :: Repository rt p wR wU wT -> Tree IO -> IO () Source #
Replace the existing pristine with a new one (loaded up in a Tree object).
readRepo :: (IsRepoType rt, RepoPatch p) => Repository rt p wR wU wT -> IO (PatchSet rt p Origin wR) Source #
Read inventories and patches from a repository and return them as a
PatchSet
. Note that patches and inventories are read lazily.
addToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> UseIndex -> 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.
addPendingDiffToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> FreeLeft (FL (PrimOf p)) -> IO () Source #
Add an FL
of patches started from the pending state to the pending patch.
TODO: add witnesses for pending so we can make the types precise: currently
the passed patch can be applied in any context, not just after pending.
tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> Compression -> Verbosity -> UpdatePending -> PatchInfoAnd rt p wT wY -> IO (Repository rt p wR wU wY) Source #
tentativelyRemovePatches :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> Compression -> UpdatePending -> FL (PatchInfoAnd rt p) wX wT -> IO (Repository rt p wR wU wX) Source #
tentativelyAddToPending :: forall rt p wR wU wT wX wY. RepoPatch p => Repository rt p wR wU wT -> FL (PrimOf p) wX wY -> IO () Source #
tentativelyAddToPending repo ps
appends ps
to the pending patch.
This fuction is unsafe because it accepts a patch that works on the tentative pending and we don't currently track the state of the tentative pending.
readTentativeRepo :: (IsRepoType rt, PatchListFormat p, ReadPatch p) => Repository rt p wR wU wT -> String -> IO (PatchSet rt p Origin wT) Source #
readRepo returns the tentative repo patchset.
withManualRebaseUpdate :: forall rt p x wR wU wT1 wT2. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT1 -> (Repository rt p wR wU wT1 -> IO (Repository rt p wR wU wT2, FL (RebaseFixup (PrimOf p)) wT2 wT1, x)) -> IO (Repository rt p wR wU wT2, x) Source #
tentativelyMergePatches :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> String -> AllowConflicts -> ExternalMerge -> WantGuiPause -> Compression -> Verbosity -> Reorder -> (UseIndex, ScanKnown, DiffAlgorithm) -> Fork (PatchSet rt p) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) Origin wR wY -> IO (Sealed (FL (PrimOf p) wU)) Source #
considerMergeToWorking :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> String -> AllowConflicts -> ExternalMerge -> WantGuiPause -> Compression -> Verbosity -> Reorder -> (UseIndex, ScanKnown, DiffAlgorithm) -> Fork (PatchSet rt p) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) Origin wR wY -> IO (Sealed (FL (PrimOf p) wU)) Source #
revertRepositoryChanges :: RepoPatch p => Repository rt p wR wU wT -> UpdatePending -> IO (Repository rt p wR wU wR) Source #
Slightly confusingly named: as well as throwing away any tentative changes, revertRepositoryChanges also re-initialises the tentative state. It's therefore used before makign any changes to the repo.
finalizeRepositoryChanges :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wT -> UpdatePending -> Compression -> IO (Repository rt p wT wU wT) Source #
Atomically copy the tentative state to the recorded state, thereby committing the tentative changes that were made so far. This includes inventories, pending, and the index.
createRepository :: PatchFormat -> WithWorkingDir -> WithPatchIndex -> UseCache -> IO EmptyRepository Source #
createRepositoryV1 :: WithWorkingDir -> WithPatchIndex -> UseCache -> IO (Repository ('RepoType 'NoRebase) (RepoPatchV1 Prim) Origin Origin Origin) Source #
createRepositoryV2 :: WithWorkingDir -> WithPatchIndex -> UseCache -> IO (Repository ('RepoType 'NoRebase) (RepoPatchV2 Prim) Origin Origin Origin) Source #
data EmptyRepository where Source #
EmptyRepository :: (RepoPatch p, ApplyState p ~ Tree) => Repository ('RepoType 'NoRebase) p Origin Origin Origin -> EmptyRepository |
cloneRepository :: String -> String -> Verbosity -> UseCache -> CloneKind -> UMask -> RemoteDarcs -> SetScriptsExecutable -> RemoteRepos -> SetDefault -> InheritDefault -> [MatchFlag] -> RepoFormat -> WithWorkingDir -> WithPatchIndex -> Bool -> ForgetParent -> IO () Source #
applyToWorking :: (ApplyState p ~ Tree, RepoPatch p) => Repository rt p wR wU wT -> Verbosity -> FL (PrimOf p) wU wY -> IO (Repository rt p wR wY wT) Source #
createPristineDirectoryTree :: Repository rt p wR wU wT -> FilePath -> WithWorkingDir -> IO () Source #
grab the pristine hash of _darcs/hash_inventory, and retrieve whole pristine tree, possibly writing a clean working tree in the process.
createPartialsPristineDirectoryTree :: Repository rt p wR wU wT -> [AnchoredPath] -> FilePath -> IO () Source #
Used by the commands dist and diff
reorderInventory :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> Compression -> IO () Source #
Writes out a fresh copy of the inventory that minimizes the amount of inventory that need be downloaded when people pull from the repository.
Specifically, it breaks up the inventory on the most recent tag. This speeds up most commands when run remotely, both because a smaller file needs to be transfered (only the most recent inventory). It also gives a guarantee that all the patches prior to a given tag are included in that tag, so less commutation and history traversal is needed. This latter issue can become very important in large repositories.
cleanRepository :: Repository rt p wR wU wT -> IO () Source #
data PatchSet rt p wStart wY Source #
The patches in a repository are stored in chunks broken up at "clean" tags. A tag is clean if the only patches before it in the current repository ordering are ones that the tag depends on (either directly or indirectly). Each chunk is stored in a separate inventory file on disk.
A PatchSet
represents a repo's history as the list of patches since the
last clean tag, and then a list of patch lists each delimited by clean tags.
Because the invariants about clean tags can only be maintained if a
PatchSet
contains the whole history, the first witness is always forced
to be Origin
. The type still has two witnesses so it can easily be used
with combinators like :>
and Fork
.
The history is lazily loaded from disk so does not normally need to be all kept in memory.
type SealedPatchSet rt p wStart = Sealed (PatchSet rt p wStart) Source #
type PatchInfoAnd rt p = PatchInfoAndG rt (Named p) Source #
setScriptsExecutable :: IO () Source #
setScriptsExecutablePatches :: PatchInspect p => p wX wY -> IO () Source #
testTentative :: Repository rt p wR wU wT -> RunTest -> LeaveTestDir -> SetScriptsExecutable -> Verbosity -> IO ExitCode Source #
modifyCache :: (Cache -> Cache) -> Repository rt p wR wU wT -> Repository rt p wR wU wT Source #
Recorded and unrecorded and pending.
readRecorded :: 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 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.
unrecordedChanges :: (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> LookForMoves -> LookForReplaces -> Repository rt p wR 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.
readPendingAndWorking :: (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown, DiffAlgorithm) -> LookForMoves -> LookForReplaces -> Repository rt p wR wU wR -> Maybe [AnchoredPath] -> IO ((FL (PrimOf p) :> FL (PrimOf p)) wR wU) Source #
:: (RepoPatch p, ApplyState p ~ Tree) | |
=> Repository rt p wR wU wR | Repository itself, used for grabbing unrecorded changes |
-> FL (PatchInfoAnd rt p) wX wR | Recorded patches from repository, starting from same context as the patches to filter |
-> 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
readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO (Tree IO) Source #
Obtains the recorded Tree
with the pending patch applied.
Index.
readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wR wU wR -> IO Index Source #
invalidateIndex :: t -> IO () Source #
Mark the existing index as invalid. This has to be called whenever the listing of pristine+pending changes and will cause darcs to update the index. This will happen either when we call updateIndex in finalizeRepositoryChanges or else when we try to read the index the next time. (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.)