Safe Haskell | None |
---|---|
Language | Haskell2010 |
- inventoriesDir :: String
- pristineDir :: String
- patchesDir :: String
- hashedInventory :: String
- revertTentativeChanges :: IO ()
- finalizeTentativeChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> Compression -> IO ()
- cleanPristine :: Repository p wR wU wT -> IO ()
- filterDirContents :: FilePath -> (FilePath -> Bool) -> IO [FilePath]
- cleanInventories :: Repository p wR wU wT -> IO ()
- cleanPatches :: Repository p wR wU wT -> IO ()
- copyPristine :: Cache -> String -> String -> WithWorkingDir -> IO ()
- copyPartialsPristine :: FilePathLike fp => Cache -> String -> String -> [fp] -> IO ()
- applyToTentativePristine :: (ApplyState p ~ Tree, Patchy p) => p wX wY -> IO ()
- addToSpecificInventory :: RepoPatch p => String -> Cache -> Compression -> PatchInfoAnd p wX wY -> IO FilePath
- addToTentativeInventory :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p wX wY -> IO FilePath
- removeFromTentativeInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> Compression -> FL (PatchInfoAnd p) wX wT -> IO ()
- readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> String -> IO (PatchSet p Origin wR)
- readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> String -> IO (PatchSet p Origin wT)
- readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p wR wU wT -> String -> IO (PatchSet p Origin wS)
- writeAndReadPatch :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p wX wY -> IO (PatchInfoAnd p wX wY)
- writeTentativeInventory :: RepoPatch p => Cache -> Compression -> PatchSet p Origin wX -> IO ()
- copyHashedInventory :: RepoPatch p => Repository p wR wU wT -> RemoteDarcs -> String -> IO ()
- readHashedPristineRoot :: Repository p wR wU wT -> IO (Maybe String)
- pris2inv :: String -> ByteString -> Doc
- inv2pris :: ByteString -> String
- copySources :: RepoPatch p => Repository p wR wU wT -> String -> IO ()
- listInventories :: IO [String]
- listInventoriesLocal :: IO [String]
- listInventoriesRepoDir :: String -> IO [String]
- listPatchesLocalBucketed :: String -> String -> IO [String]
- writePatchIfNecessary :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p wX wY -> IO (PatchInfo, String)
- readRepoFromInventoryList :: (RepoPatch p, ApplyState p ~ Tree) => Cache -> (Maybe String, [(PatchInfo, String)]) -> IO (SealedPatchSet p Origin)
- readPatchIds :: ByteString -> [(PatchInfo, String)]
- set :: [String] -> Set ByteString
- unset :: Set ByteString -> [String]
Documentation
revertTentativeChanges :: 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, ApplyState p ~ Tree) => Repository p wR wU wT -> Compression -> 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.
cleanPristine :: Repository p wR wU wT -> IO () Source
cleanPristine removes any obsolete (unreferenced) entries in the pristine cache.
filterDirContents :: FilePath -> (FilePath -> Bool) -> IO [FilePath] Source
filterDirContents returns the contents of the directory d
except files whose names begin with .
(directories . and ..,
hidden files) and files whose names are filtered by the function f
, if
dir
is empty, no paths are returned.
cleanInventories :: Repository p wR wU wT -> IO () Source
cleanInventories removes any obsolete (unreferenced) files in the inventories directory.
cleanPatches :: Repository p wR wU wT -> IO () Source
cleanPatches removes any obsolete (unreferenced) files in the patches directory.
copyPristine :: Cache -> String -> String -> WithWorkingDir -> IO () Source
copyPristine copies a pristine tree into the current pristine dir, and possibly copies a clean working copy. The target is read from the passed-in dir/inventory name combination.
copyPartialsPristine :: FilePathLike fp => Cache -> String -> String -> [fp] -> IO () Source
copyPartialsPristine copies the pristine entries for a given list of filepaths.
applyToTentativePristine :: (ApplyState p ~ Tree, Patchy p) => p wX wY -> IO () Source
applyToTentativePristine applies a patch p
to the tentative pristine
tree, and updates the tentative pristine hash
addToSpecificInventory :: RepoPatch p => String -> Cache -> Compression -> PatchInfoAnd p wX wY -> IO FilePath Source
addToSpecificInventory adds a patch to a specific inventory file, and returns the FilePath whichs corresponds to the written-out patch.
addToTentativeInventory :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p wX wY -> IO FilePath Source
removeFromTentativeInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> Compression -> FL (PatchInfoAnd p) wX wT -> IO () Source
removeFromTentativeInventory attempts to remove an FL of patches from the tentative inventory. This is used for commands that wish to modify already-recorded patches.
readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> String -> IO (PatchSet p Origin wR) Source
readRepo returns the "current" repo patchset.
readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p wR wU wT -> String -> IO (PatchSet p Origin wT) Source
readRepo returns the tentative repo patchset.
readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p wR wU wT -> String -> IO (PatchSet p Origin wS) Source
readRepoUsingSpecificInventory uses the inventory at invPath
to read the
repository repo
.
writeAndReadPatch :: RepoPatch p => Cache -> Compression -> 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 => Cache -> Compression -> PatchSet p Origin wX -> IO () Source
writeTentativeInventory writes patchSet
as the tentative inventory.
copyHashedInventory :: RepoPatch p => Repository p wR wU wT -> RemoteDarcs -> String -> IO () Source
copyRepo copies the hashed inventory of repo
to the repository located at
remote
.
readHashedPristineRoot :: Repository p wR wU wT -> IO (Maybe String) Source
readHashedPristineRoot attempts to read the pristine hash from the current inventory, returning Nothing if it cannot do so.
pris2inv :: String -> ByteString -> Doc Source
pris2inv takes an updated pristine hash and an inventory, and outputs the new pristine hash followed by the original inventory (having skipped the old inventory hash).
inv2pris :: ByteString -> String Source
inv2pris takes the content of an inventory, and extracts the corresponding pristine hash from the inventory (the hash is prefixed by "pristine:").
copySources :: RepoPatch p => Repository p wR wU wT -> String -> IO () Source
copySources
copies the prefs/sources file to the local repo, from the
remote, having first filtered the local filesystem sources.
listInventories :: IO [String] Source
listInventories returns a list of the inventories hashes. This function attempts to retrieve missing inventory files.
listInventoriesLocal :: IO [String] Source
listInventoriesLocal returns a list of the inventories hashes. This function does not attempt to retrieve missing inventory files.
listInventoriesRepoDir :: String -> IO [String] Source
listInventoriesRepoDir returns a list of the inventories hashes.
The argument repoDir
is the directory of the repository from which
we are going to read the "hashed_inventory" file.
The rest of hashed files are read from the global cache.
listPatchesLocalBucketed :: String -> String -> IO [String] Source
listPatchesLocalBucketed is similar to listPatchesLocal, but
it read the inventory directory under darcsDir
in bucketed format.
writePatchIfNecessary :: RepoPatch p => Cache -> Compression -> PatchInfoAnd p wX wY -> IO (PatchInfo, String) Source
writeHashIfNecessary writes the patch and returns the resulting info/hash, if it has not already been written. If it has been written, we have the hash in the PatchInfoAnd, so we extract and return the info/hash.
readRepoFromInventoryList :: (RepoPatch p, ApplyState p ~ Tree) => Cache -> (Maybe String, [(PatchInfo, String)]) -> IO (SealedPatchSet p Origin) Source
readRepoFromInventoryList allows the caller to provide an optional "from inventory" hash, and a list of info/hash pairs that identify a list of patches, returning a patchset of the resulting repo.
readPatchIds :: ByteString -> [(PatchInfo, String)] Source
'readPatchIds inventory' parses the content of a hashed_inventory file after the "pristine:" and "Starting with inventory:" header lines have been removed. The second value in the resulting tuples is the file hash of the associated patch (the "hash:" line).
set :: [String] -> Set ByteString Source
set converts a list of strings into a set of Char8 ByteStrings for faster Set operations.
unset :: Set ByteString -> [String] Source
unset is the inverse of set.