darcs-2.1.98.2: a distributed, interactive, smart revision control systemSource codeContentsIndex
Darcs.Repository
Synopsis
data Repository p
($-) :: ((forall p. RepoPatch p => Repository p -> IO a) -> IO a) -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (Either String (Repository p))
identifyRepositoryFor :: forall p. RepoPatch p => Repository p -> String -> IO (Repository p)
withRepoLock :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
withRepoReadLock :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
withRepository :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
withRepositoryDirectory :: forall a. [DarcsFlag] -> String -> (forall p. RepoPatch p => Repository p -> IO a) -> IO a
withGutsOf :: Repository p -> IO () -> IO ()
makePatchLazy :: RepoPatch p => Repository p -> PatchInfoAnd p -> IO (PatchInfoAnd p)
writePatchSet :: RepoPatch p => PatchSet p -> [DarcsFlag] -> IO (Repository p)
findRepository :: [DarcsFlag] -> IO (Either String ())
amInRepository :: [DarcsFlag] -> IO (Either String ())
amNotInRepository :: [DarcsFlag] -> IO (Either String ())
slurp_pending :: RepoPatch p => Repository p -> IO Slurpy
replacePristine :: Repository p -> FilePath -> IO ()
replacePristineFromSlurpy :: Repository p -> Slurpy -> IO ()
slurp_recorded :: RepoPatch p => Repository p -> IO Slurpy
slurp_recorded_and_unrecorded :: RepoPatch p => Repository p -> IO (Slurpy, Slurpy)
withRecorded :: RepoPatch p => Repository p -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a
get_unrecorded :: RepoPatch p => Repository p -> IO (FL Prim)
get_unrecorded_unsorted :: RepoPatch p => Repository p -> IO (FL Prim)
get_unrecorded_no_look_for_adds :: RepoPatch p => Repository p -> [FileName] -> IO (FL Prim)
get_unrecorded_in_files :: RepoPatch p => Repository p -> [FileName] -> IO (FL Prim)
read_repo :: RepoPatch p => Repository p -> IO (PatchSet p)
sync_repo :: Repository p -> IO ()
prefsUrl :: Repository p -> String
add_to_pending :: RepoPatch p => Repository p -> FL Prim -> IO ()
tentativelyAddPatch :: RepoPatch p => Repository p -> [DarcsFlag] -> PatchInfoAnd p -> IO ()
tentativelyRemovePatches :: RepoPatch p => Repository p -> [DarcsFlag] -> FL (Named p) -> IO ()
tentativelyAddToPending :: forall p. RepoPatch p => Repository p -> [DarcsFlag] -> FL Prim -> IO ()
tentativelyReplacePatches :: forall p. RepoPatch p => Repository p -> [DarcsFlag] -> FL (Named p) -> IO ()
tentativelyMergePatches :: RepoPatch p => Repository p -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) -> FL (PatchInfoAnd p) -> IO (Sealed (FL Prim))
considerMergeToWorking :: RepoPatch p => Repository p -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) -> FL (PatchInfoAnd p) -> IO (Sealed (FL Prim))
revertRepositoryChanges :: RepoPatch p => Repository p -> IO ()
finalizeRepositoryChanges :: RepoPatch p => Repository p -> IO ()
createRepository :: [DarcsFlag] -> IO ()
copyRepository :: RepoPatch p => Repository p -> IO ()
copy_oldrepo_patches :: RepoPatch p => [DarcsFlag] -> Repository p -> FilePath -> IO ()
patchSetToRepository :: RepoPatch p => Repository p -> PatchSet p -> [DarcsFlag] -> IO (Repository p)
unrevertUrl :: Repository p -> String
applyToWorking :: Patchy p => Repository p1 -> [DarcsFlag] -> p -> IO ()
patchSetToPatches :: RepoPatch p => RL (RL (PatchInfoAnd p)) -> FL (Named p)
createPristineDirectoryTree :: RepoPatch p => Repository p -> FilePath -> IO ()
createPartialsPristineDirectoryTree :: (FilePathLike fp, RepoPatch p) => Repository p -> [fp] -> FilePath -> IO ()
optimizeInventory :: RepoPatch p => Repository p -> IO ()
cleanRepository :: RepoPatch p => Repository p -> IO ()
checkPristineAgainstSlurpy :: RepoPatch p => Repository p -> Slurpy -> IO Bool
getMarkedupFile :: RepoPatch p => Repository p -> PatchInfo -> FilePath -> IO MarkedUpFile
type PatchSet p = RL (RL (PatchInfoAnd p))
type SealedPatchSet p = Sealed (RL (RL (PatchInfoAnd p)))
data PatchInfoAnd p
setScriptsExecutable :: IO ()
checkUnrelatedRepos :: [DarcsFlag] -> [PatchInfo] -> PatchSet p -> PatchSet p -> IO ()
testTentative :: RepoPatch p => Repository p -> IO ()
testRecorded :: RepoPatch p => Repository p -> IO ()
Documentation
data Repository p Source
show/hide Instances
($-) :: ((forall p. RepoPatch p => Repository p -> IO a) -> IO a) -> (forall p. RepoPatch p => Repository p -> IO a) -> IO aSource
maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (Either String (Repository p))Source
identifyRepositoryFor :: forall p. RepoPatch p => Repository p -> String -> IO (Repository p)Source
withRepoLock :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO aSource
withRepoReadLock :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO aSource
withRepository :: [DarcsFlag] -> (forall p. RepoPatch p => Repository p -> IO a) -> IO aSource
withRepositoryDirectory :: forall a. [DarcsFlag] -> String -> (forall p. RepoPatch p => Repository p -> IO a) -> IO aSource
withGutsOf :: Repository p -> IO () -> IO ()Source
makePatchLazy :: RepoPatch p => Repository p -> PatchInfoAnd p -> IO (PatchInfoAnd p)Source
writePatchSet :: RepoPatch p => PatchSet p -> [DarcsFlag] -> IO (Repository p)Source
writePatchSet is like patchSetToRepository, except that it doesn't touch the working directory or pristine cache.
findRepository :: [DarcsFlag] -> IO (Either String ())Source
amInRepository :: [DarcsFlag] -> IO (Either String ())Source
amNotInRepository :: [DarcsFlag] -> IO (Either String ())Source
slurp_pending :: RepoPatch p => Repository p -> IO SlurpySource
replacePristine :: Repository p -> FilePath -> IO ()Source
replacePristineFromSlurpy :: Repository p -> Slurpy -> IO ()Source
slurp_recorded :: RepoPatch p => Repository p -> IO SlurpySource
slurp_recorded_and_unrecorded :: RepoPatch p => Repository p -> IO (Slurpy, Slurpy)Source
withRecorded :: RepoPatch p => Repository p -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO aSource
get_unrecorded :: RepoPatch p => Repository p -> IO (FL Prim)Source
get_unrecorded_unsorted :: RepoPatch p => Repository p -> IO (FL Prim)Source
get_unrecorded_no_look_for_adds :: RepoPatch p => Repository p -> [FileName] -> IO (FL Prim)Source
get_unrecorded_in_files :: RepoPatch p => Repository p -> [FileName] -> IO (FL Prim)Source
Gets the unrecorded changes in the given paths in the current repository.
read_repo :: RepoPatch p => Repository p -> IO (PatchSet p)Source
sync_repo :: Repository p -> IO ()Source
prefsUrl :: Repository p -> StringSource
add_to_pending :: RepoPatch p => Repository p -> FL Prim -> IO ()Source
tentativelyAddPatch :: RepoPatch p => Repository p -> [DarcsFlag] -> PatchInfoAnd p -> IO ()Source
tentativelyRemovePatches :: RepoPatch p => Repository p -> [DarcsFlag] -> FL (Named p) -> IO ()Source
tentativelyAddToPending :: forall p. RepoPatch p => Repository p -> [DarcsFlag] -> FL Prim -> IO ()Source
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.
tentativelyReplacePatches :: forall p. RepoPatch p => Repository p -> [DarcsFlag] -> FL (Named p) -> IO ()Source
tentativelyMergePatches :: RepoPatch p => Repository p -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) -> FL (PatchInfoAnd p) -> IO (Sealed (FL Prim))Source
considerMergeToWorking :: RepoPatch p => Repository p -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) -> FL (PatchInfoAnd p) -> IO (Sealed (FL Prim))Source
revertRepositoryChanges :: RepoPatch p => Repository p -> IO ()Source
finalizeRepositoryChanges :: RepoPatch p => Repository p -> IO ()Source
createRepository :: [DarcsFlag] -> IO ()Source
copyRepository :: RepoPatch p => Repository p -> IO ()Source
copy_oldrepo_patches :: RepoPatch p => [DarcsFlag] -> Repository p -> FilePath -> IO ()Source
patchSetToRepository :: RepoPatch p => Repository p -> PatchSet p -> [DarcsFlag] -> IO (Repository p)Source
patchSetToRepository takes a patch set, and writes a new repository in the current directory that contains all the patches in the patch set. This function is used when 'darcs get'ing a repository with the --to-match flag and the new repository is not in hashed format. This function does not (yet) work for hashed repositories. If the passed DarcsFlags tell darcs to create a hashed repository, this function will call error.
unrevertUrl :: Repository p -> StringSource
applyToWorking :: Patchy p => Repository p1 -> [DarcsFlag] -> p -> IO ()Source
patchSetToPatches :: RepoPatch p => RL (RL (PatchInfoAnd p)) -> FL (Named p)Source
createPristineDirectoryTree :: RepoPatch p => Repository p -> FilePath -> IO ()Source
createPartialsPristineDirectoryTree :: (FilePathLike fp, RepoPatch p) => Repository p -> [fp] -> FilePath -> IO ()Source
optimizeInventory :: RepoPatch p => Repository p -> IO ()Source
cleanRepository :: RepoPatch p => Repository p -> IO ()Source
checkPristineAgainstSlurpy :: RepoPatch p => Repository p -> Slurpy -> IO BoolSource
getMarkedupFile :: RepoPatch p => Repository p -> PatchInfo -> FilePath -> IO MarkedUpFileSource
type PatchSet p = RL (RL (PatchInfoAnd p))Source

A PatchSet is in reverse order, plus has information about which tags are clean, meaning all patches applied prior to them are in the tag itself, so we can stop reading at that point. Just to clarify, the first patch in a PatchSet is the one most recently applied to the repo.

PatchSets have the property that if (info $ last $ head a) == (info $ last $ head b) then (tail a) and (tail b) are identical repositories

Questions:

Does this mean that in a patch set such as [[a b t1 c d e t2][f g t3] [h i]], t1, t2 and t3 are tags, and t2 and t3 are clean?

Can we have PatchSet with length at least 3? Florent

type SealedPatchSet p = Sealed (RL (RL (PatchInfoAnd p)))Source
data PatchInfoAnd p Source
PatchInfoAnd p represents a hope we have to get a patch through its info. We're not sure we have the patch, but we know its info.
show/hide Instances
setScriptsExecutable :: IO ()Source
Sets scripts in or below the current directory executable. A script is any file that starts with the bytes '#!'. This is used sometimes for --set-scripts-executable, but at other times --set-scripts-executable is handled by the hunk patch case of applyFL.
checkUnrelatedRepos :: [DarcsFlag] -> [PatchInfo] -> PatchSet p -> PatchSet p -> IO ()Source
testTentative :: RepoPatch p => Repository p -> IO ()Source
testRecorded :: RepoPatch p => Repository p -> IO ()Source
Produced by Haddock version 2.4.2