Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- revertTentativeChanges :: Repository 'RO p wU wR -> IO ()
- finalizeTentativeChanges :: RepoPatch p => Repository 'RW p wU wR -> IO ()
- addToTentativeInventory :: RepoPatch p => Cache -> PatchInfoAnd p wX wY -> IO ()
- readPatches :: RepoPatch p => Repository rt p wU wR -> IO (PatchSet p Origin wR)
- readTentativePatches :: (PatchListFormat p, ReadPatch p) => Repository 'RW p wU wR -> IO (PatchSet p Origin wR)
- writeAndReadPatch :: RepoPatch p => Cache -> PatchInfoAnd p wX wY -> IO (PatchInfoAnd p wX wY)
- writeTentativeInventory :: RepoPatch p => Repository 'RW p wU wR -> PatchSet p Origin wX -> IO ()
- copyHashedInventory :: Repository 'RO p wU wR -> RemoteDarcs -> String -> IO ()
- writePatchIfNecessary :: RepoPatch p => Cache -> PatchInfoAnd p wX wY -> IO InventoryEntry
- tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> UpdatePending -> PatchInfoAnd p wR wY -> IO (Repository 'RW p wU wY)
- tentativelyRemovePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wX wR -> IO (Repository 'RW p wU wX)
- tentativelyRemovePatches_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wX wR -> IO (Repository 'RW p wU wX)
- tentativelyAddPatch_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository 'RW p wU wR -> UpdatePending -> PatchInfoAnd p wR wY -> IO (Repository 'RW p wU wY)
- tentativelyAddPatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wR wY -> IO (Repository 'RW p wU wY)
- tentativelyAddPatches_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wR wY -> IO (Repository 'RW p wU wY)
- reorderInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> OptimizeDeep -> IO ()
- data UpdatePristine
- repoXor :: RepoPatch p => Repository rt p wU wR -> IO SHA1
Documentation
revertTentativeChanges :: Repository 'RO p wU wR -> IO () Source #
revertTentativeChanges swaps the tentative and "real" hashed inventory files, and then updates the tentative pristine with the "real" inventory hash.
finalizeTentativeChanges :: RepoPatch p => Repository 'RW p wU wR -> IO () Source #
finalizeTentativeChanges trys to atomically swap the tentative inventory/pristine pointers with the "real" pointers; it first re-reads the inventory to optimize it, presumably to take account of any new tags, and then writes out the new tentative inventory, and finally does the atomic swap. In general, we can't clean the pristine cache at the same time, since a simultaneous get might be in progress.
addToTentativeInventory :: RepoPatch p => Cache -> PatchInfoAnd p wX wY -> IO () Source #
Add (append) a patch to the tentative inventory.
Warning: this allows to add any arbitrary patch!
Used by convert import and tentativelyAddPatch_
.
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.
readTentativePatches :: (PatchListFormat p, ReadPatch p) => Repository 'RW p wU wR -> IO (PatchSet p Origin wR) Source #
Read the tentative PatchSet
of a (hashed) Repository
.
writeAndReadPatch :: RepoPatch p => Cache -> PatchInfoAnd p wX wY -> IO (PatchInfoAnd p wX wY) Source #
writeAndReadPatch makes a patch lazy, by writing it out to disk (thus forcing it), and then re-reads the patch lazily.
writeTentativeInventory :: RepoPatch p => Repository 'RW p wU wR -> PatchSet p Origin wX -> IO () Source #
Write a PatchSet
to the tentative inventory.
copyHashedInventory :: Repository 'RO p wU wR -> RemoteDarcs -> String -> IO () Source #
Copy the hashed inventory from the given location to the given repository, possibly using the given remote darcs binary.
writePatchIfNecessary :: RepoPatch p => Cache -> PatchInfoAnd p wX wY -> IO InventoryEntry Source #
Write a PatchInfoAnd
to disk and return an InventoryEntry
i.e. the
patch info and hash. However, if we patch already contains a hash, assume it
has already been written to disk at some point and merely return the info
and hash.
tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> UpdatePending -> PatchInfoAnd p wR wY -> IO (Repository 'RW p wU wY) Source #
tentativelyRemovePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wX wR -> IO (Repository 'RW p wU wX) Source #
tentativelyRemovePatches_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wX wR -> IO (Repository 'RW p wU wX) Source #
tentativelyAddPatch_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository 'RW p wU wR -> UpdatePending -> PatchInfoAnd p wR wY -> IO (Repository 'RW p wU wY) Source #
tentativelyAddPatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wR wY -> IO (Repository 'RW p wU wY) Source #
tentativelyAddPatches_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository 'RW p wU wR -> UpdatePending -> FL (PatchInfoAnd p) wR wY -> IO (Repository 'RW p wU wY) Source #
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 UpdatePristine Source #
Instances
Eq UpdatePristine Source # | |
Defined in Darcs.Repository.Hashed (==) :: UpdatePristine -> UpdatePristine -> Bool # (/=) :: UpdatePristine -> UpdatePristine -> Bool # |
repoXor :: RepoPatch p => Repository rt p wU wR -> IO SHA1 Source #
XOR of all hashes of the patches' metadata. It enables to quickly see whether two repositories have the same patches, independently of their order. It relies on the assumption that the same patch cannot be present twice in a repository. This checksum is not cryptographically secure, see http://robotics.stanford.edu/~xb/crypto06b/ .