darcs-2.18.2: a distributed, interactive, smart revision control system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Darcs.Repository

Synopsis

Documentation

data Repository (rt :: AccessType) (p :: * -> * -> *) wU wR Source #

A Repository is a token representing the state of a repository on disk. It is parameterized by

rt
the access type (whether we are in a transaction or not),
p
the patch type,
wU
the witness for the unrecorded state (what's in the working tree now).
wR
the witness for
  • the recorded state when outside a transaction, or
  • the tentative state when inside a transaction.

data AccessType Source #

Constructors

RO 
RW 

Instances

Instances details
Eq AccessType Source # 
Instance details

Defined in Darcs.Repository.InternalTypes

repoCache :: Repository rt p wU wR -> Cache Source #

data HashedDir Source #

Semantically, this is the type of hashed objects. Git has a type tag inside the hashed file itself, whereas in Darcs the type is determined by the subdirectory.

Instances

Instances details
Eq HashedDir Source # 
Instance details

Defined in Darcs.Util.ValidHash

data Cache Source #

Cache is an abstract type for hiding the underlying cache locations

Instances

Instances details
Show Cache Source # 
Instance details

Defined in Darcs.Util.Cache

Methods

showsPrec :: Int -> Cache -> ShowS #

show :: Cache -> String #

showList :: [Cache] -> ShowS #

data CacheLoc Source #

Instances

Instances details
Eq CacheLoc Source #

Note: this non-structural instance ignores the cacheWritable field. This is so that when we nub a list of locations we retain only one (the first) variant.

Instance details

Defined in Darcs.Util.Cache

data CacheType Source #

Constructors

Repo 
Directory 

Instances

Instances details
Show CacheType Source # 
Instance details

Defined in Darcs.Util.Cache

Eq CacheType Source # 
Instance details

Defined in Darcs.Util.Cache

data WritableOrNot Source #

Constructors

Writable 
NotWritable 

Instances

Instances details
Show WritableOrNot Source # 
Instance details

Defined in Darcs.Util.Cache

Eq WritableOrNot Source # 
Instance details

Defined in Darcs.Util.Cache

mkCache :: [CacheLoc] -> Cache Source #

Smart constructor for CacheLoc.

reportBadSources :: IO () Source #

Prints an error message with a list of bad caches.

data RepoJob rt a Source #

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.

Constructors

RepoJob (TreePatchJob rt a)

The most common RepoJob; the underlying action can accept any patch whose ApplyState is Tree.

V1Job (V1PatchJob rt a)

A job that only works on darcs 1 patches

V2Job (V2PatchJob rt a)

A job that only works on darcs 2 patches

PrimV1Job (PrimV1PatchJob rt a)

A job that works on any repository where the patch type p has PrimOf p = Prim. This was added to support darcsden, which inspects the internals of V1 prim patches. In future it should be replaced with a more abstract inspection API as part of PrimPatch.

OldRebaseJob (TreePatchJob rt a)

A job that works even if there is an old-style rebase in progress.

maybeIdentifyRepository :: UseCache -> String -> IO (IdentifyRepo 'RO p wU wR) Source #

Try to identify the repository at a given location, passed as a String. If the lcation is ".", then we assume we are identifying the local repository. Otherwise we assume we are dealing with a remote repo, which could be a URL or an absolute path.

identifyRepositoryFor :: ReadingOrWriting -> Repository rt p wU wR -> UseCache -> String -> IO (Repository 'RO p vR vU) Source #

identifyRepositoryFor repo url identifies (and returns) the repo at url, but fails if it is not compatible for reading from and writing to.

withRepoLock :: UseCache -> UMask -> RepoJob 'RW 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.

withRepoLockCanFail :: UseCache -> RepoJob 'RO () -> 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 'RO a -> IO a Source #

apply a given RepoJob to a repository in the current working directory

withRepositoryLocation :: UseCache -> String -> RepoJob 'RO a -> IO a Source #

apply a given RepoJob to a repository in a given url

writePristine :: Repository rt p wU wR -> Tree IO -> IO PristineHash Source #

Replace the existing pristine with a new one (loaded up in a Tree object). Warning: If rt ~ 'RO this overwrites the recorded state, use only when creating a new repo!

readPatches :: RepoPatch p => Repository rt p wU wR -> IO (PatchSet 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 '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.

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.

setTentativePending :: forall p wU wR wP. RepoPatch p => Repository 'RW p wU wR -> FL (PrimOf p) wR wP -> IO () Source #

Overwrites the pending patch with a new one, starting at the tentative state.

tentativelyRemoveFromPW :: forall p wR wO wP wU. RepoPatch p => Repository 'RW p wU wR -> FL (PrimOf p) wO wR -> FL (PrimOf p) wO wP -> FL (PrimOf p) wP wU -> IO () Source #

Remove as much as possible of the given list of prim patches from the pending patch. It is used by record and amend to update pending.

The "as much as possible" is due to --look-for-* options which cause changes that normally must be explicitly done by the user (such as add, move, and replace) to be inferred from the the diff between pristine and working. Also, before we present prims to the user to select for recording, we coalesce prims from pending and working, which is reason we have to use decoalescing.

withManualRebaseUpdate :: RepoPatch p => Repository rt p wU wR -> (Repository rt p wU wR -> IO (Repository rt p wU wR', FL (RebaseFixup (PrimOf p)) wR' wR, x)) -> IO (Repository rt p wU wR', x) Source #

revertRepositoryChanges :: RepoPatch p => Repository 'RO p wU wR -> IO (Repository 'RW p 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 :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> DryRun -> IO (Repository 'RO p wU wR) Source #

Atomically copy the tentative state to the recorded state, thereby committing the tentative changes that were made so far. This includes inventories, pending, rebase, and the index.

applyToWorking :: (ApplyState p ~ Tree, RepoPatch p) => Repository rt p wU wR -> Verbosity -> FL (PrimOf p) wU wY -> IO (Repository rt p wY wR) Source #

createPristineDirectoryTree :: Repository rt p wU wR -> FilePath -> WithWorkingDir -> IO () Source #

Write the pristine tree into a plain directory at the given path.

reorderInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> OptimizeDeep -> 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. The exact beavior depends on the 3rd parameter:

For OptimizeShallow 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.

For OptimizeDeep, the whole repo is traversed, from oldest to newest patch. Every tag we encounter is made clean, but only if that doesn't make any previous clean tag unclean. Every clean tags gets its own inventory. This speeds up "deep" operations, too, such as cloning a specific tag. It does not necessarily make the latest tag clean, but the benefits are similar to the shallow case.

data PatchSet 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.

Instances

Instances details
Ident (PatchSet p) Source # 
Instance details

Defined in Darcs.Patch.Set

Methods

ident :: PatchSet p wX wY -> PatchId (PatchSet p) Source #

Show2 p => Show2 (PatchSet p) Source # 
Instance details

Defined in Darcs.Patch.Set

Methods

showDict2 :: ShowDict (PatchSet p wX wY) Source #

Show2 p => Show1 (PatchSet p wStart) Source # 
Instance details

Defined in Darcs.Patch.Set

Methods

showDict1 :: Dict (Show (PatchSet p wStart wX)) Source #

Show2 p => Show (PatchSet p wStart wY) Source # 
Instance details

Defined in Darcs.Patch.Set

Methods

showsPrec :: Int -> PatchSet p wStart wY -> ShowS #

show :: PatchSet p wStart wY -> String #

showList :: [PatchSet p wStart wY] -> ShowS #

type PatchId (PatchSet p) Source # 
Instance details

Defined in Darcs.Patch.Set

type SealedPatchSet p wStart = Sealed (PatchSet p wStart) Source #

modifyCache :: (Cache -> Cache) -> Repository rt p wU wR -> Repository rt p wU wR Source #

Recorded and unrecorded and pending.

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.

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.

filterOutConflicts Source #

Arguments

:: (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

readPristineAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository rt p wU wR -> IO (Tree IO) Source #

Obtains the recorded Tree with the pending patch applied.