darcs-2.10.1: a distributed, interactive, smart revision control system

Safe HaskellNone
LanguageHaskell2010

Darcs.Repository.Internal

Synopsis

Documentation

data Repository 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 directory 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 p wRecordedstate wUnrecordedstate wTentativestate) 

maybeIdentifyRepository :: UseCache -> String -> IO (IdentifyRepo p wR wU wT) Source

Tries to identify the repository in a given directory

identifyRepository :: forall p wR wU wT. UseCache -> String -> IO (Repository p wR wU wT) Source

identifyRepository identifies the repo at url. Warning: you have to know what kind of patches are found in that repo.

identifyRepositoryFor :: forall p wR wU wT vR vU vT. RepoPatch p => Repository p wR wU wT -> UseCache -> String -> IO (Repository 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.

data IdentifyRepo p wR wU wT Source

The status of a given directory: is it a darcs repository?

Constructors

BadRepository String

looks like a repository with some error

NonRepository String

safest guess

GoodRepository (Repository p wR wU wT) 

revertRepositoryChanges :: RepoPatch p => Repository p wR wU wT -> UpdateWorking -> IO () 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.

setTentativePending :: forall p wR wU wT wX wY. RepoPatch p => Repository p wR wU wT -> UpdateWorking -> FL (PrimOf p) wX wY -> IO () Source

setTentativePending is basically unsafe. It overwrites the pending state with a new one, not related to the repository state.

checkUnrecordedConflicts :: forall p wT wY. RepoPatch p => UpdateWorking -> FL (Named p) wT wY -> IO Bool Source

readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> IO (PatchSet p Origin wR) Source

prefsUrl :: Repository p wR wU wT -> String Source

withRecorded :: RepoPatch p => Repository p wR wU wT -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a Source

withTentative :: forall p a wR wU wT. (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a Source

tentativelyRemovePatches_ :: forall p wR wU wT wX. (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository p wR wU wT -> Compression -> UpdateWorking -> FL (PatchInfoAnd p) wX wT -> IO (Repository p wR wU wX) Source

tentativelyRemoveFromPending :: forall p wR wU wT wX wY. RepoPatch p => Repository p wR wU wT -> UpdateWorking -> PatchInfoAnd p wX wY -> IO () Source

tentativelyRemoveFromPending p is used by Darcs whenever it adds a patch to the repository (eg. with apply or record). Think of it as one part of transferring patches from pending to somewhere else.

Question (Eric Kow): how do we detect patch equivalence?

tentativelyAddToPending :: forall p wR wU wT wX wY. RepoPatch p => Repository p wR wU wT -> UpdateWorking -> FL (PrimOf p) wX wY -> IO () Source

tentativelyAddToPending repo NoDryRun YesUpdateWorking pend ps appends ps to the pending patch.

It has no effect with NoUpdateWorking.

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.

tentativelyAddPatch_ :: forall p wR wU wT wY. (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository p wR wU wT -> Compression -> Verbosity -> UpdateWorking -> PatchInfoAnd p wT wY -> IO (Repository p wR wU wY) Source

tentativelyAddPatches_ :: forall p wR wU wT wY. (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository p wR wU wT -> Compression -> Verbosity -> UpdateWorking -> FL (PatchInfoAnd p) wT wY -> IO (Repository p wR wU wY) Source

tentativelyReplacePatches :: forall p wR wU wT wX. (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> Compression -> UpdateWorking -> Verbosity -> FL (PatchInfoAnd p) wX wT -> IO () Source

Given a sequence of patches anchored at the end of the current repository, actually pull them to the end of the repository by removing any patches with the same name and then adding the passed in sequence. Typically callers will have obtained the passed in sequence using findCommon and friends.

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

patchSetToPatches :: RepoPatch p => PatchSet p wX wY -> FL (Named p) wX wY Source

createPristineDirectoryTree :: RepoPatch p => Repository 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 copy in the process.

createPartialsPristineDirectoryTree :: (FilePathLike fp, RepoPatch p) => Repository p wR wU wT -> [fp] -> FilePath -> IO () Source

Used by the commands dist and diff

reorderInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wR -> Compression -> UpdateWorking -> Verbosity -> 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 :: RepoPatch p => Repository p wR wU wT -> IO () Source

makeNewPending :: forall p wR wU wT wY. (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> UpdateWorking -> FL (PrimOf p) wT wY -> IO () Source

makeNewPending repo YesUpdateWorking pendPs verifies that the pendPs could be applied to pristine if we wanted to, and if so writes it to disk. If it can't be applied, pendPs must be somehow buggy, so we save it for forensics and crash.

seekRepo :: IO (Maybe (Either String ())) Source

hunt upwards for the darcs repository This keeps changing up one parent directory, testing at each step if the current directory is a repository or not. $ The result is: Nothing, if no repository found Just (Left errorMessage), if bad repository found Just (Right ()), if good repository found. WARNING this changes the current directory for good if matchFn succeeds