Safe Haskell | Safe-Infered |
---|
- data Repository p recordedstate unrecordedstate tentativestate
- data HashedDir
- newtype Cache = Ca [CacheLoc]
- data CacheLoc = Cache {}
- data WritableOrNot
- = Writable
- | NotWritable
- data RepoJob a
- = RepoJob (forall p r u. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => Repository p r u r -> IO a)
- | V1Job (forall r u. Repository (Patch Prim) r u r -> IO a)
- | V2Job (forall r u. Repository (RealPatch Prim) r u r -> IO a)
- maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (IdentifyRepo p r u t)
- identifyRepositoryFor :: forall p r u t. RepoPatch p => Repository p r u t -> String -> IO (Repository p r u t)
- withRepoLock :: [DarcsFlag] -> RepoJob a -> IO a
- withRepoReadLock :: [DarcsFlag] -> RepoJob a -> IO a
- withRepository :: [DarcsFlag] -> RepoJob a -> IO a
- withRepositoryDirectory :: forall a. [DarcsFlag] -> String -> RepoJob a -> IO a
- withGutsOf :: Repository p r u t -> IO a -> IO a
- makePatchLazy :: RepoPatch p => Repository p r u t -> PatchInfoAnd p x y -> IO (PatchInfoAnd p x y)
- writePatchSet :: (RepoPatch p, ApplyState p ~ Tree) => PatchSet p Origin x -> [DarcsFlag] -> IO (Repository p r u t)
- findRepository :: [DarcsFlag] -> IO (Either String ())
- amInRepository :: [DarcsFlag] -> IO (Either String ())
- amNotInRepository :: [DarcsFlag] -> IO (Either String ())
- amInHashedRepository :: [DarcsFlag] -> IO (Either String ())
- replacePristine :: Repository p r u t -> Tree IO -> IO ()
- withRecorded :: RepoPatch p => Repository p r u t -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO a
- readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin r)
- prefsUrl :: Repository p r u t -> String
- readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> IO (PatchSet p Origin t)
- addToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) u y -> IO ()
- tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> PatchInfoAnd p t y -> IO (Repository p r u y)
- tentativelyRemovePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u x)
- tentativelyAddToPending :: forall p r u t x y. RepoPatch p => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) x y -> IO ()
- tentativelyReplacePatches :: forall p r u t x. (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u t)
- readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin t)
- tentativelyMergePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u))
- considerMergeToWorking :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u))
- revertRepositoryChanges :: RepoPatch p => Repository p r u t -> IO ()
- finalizeRepositoryChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ()
- createRepository :: [DarcsFlag] -> IO ()
- copyRepository :: forall p r u t. (RepoPatch p, ApplyState (PrimOf p) ~ Tree, ApplyState p ~ Tree) => Repository p r u t -> Bool -> IO ()
- patchSetToRepository :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r1 u1 r1 -> PatchSet p Origin x -> [DarcsFlag] -> IO (Repository p r u t)
- unrevertUrl :: Repository p r u t -> String
- applyToWorking :: (ApplyState (PrimOf p) ~ Tree, RepoPatch p) => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) u y -> IO (Repository p r y t)
- patchSetToPatches :: RepoPatch p => PatchSet p x y -> FL (Named p) x y
- createPristineDirectoryTree :: RepoPatch p => Repository p r u t -> FilePath -> IO ()
- createPartialsPristineDirectoryTree :: (FilePathLike fp, RepoPatch p) => Repository p r u t -> [fp] -> FilePath -> IO ()
- optimizeInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ()
- cleanRepository :: RepoPatch p => Repository p r u t -> IO ()
- data PatchSet p start y
- type SealedPatchSet p start = Sealed (PatchSet p start)
- data PatchInfoAnd p a b
- setScriptsExecutable :: IO ()
- setScriptsExecutablePatches :: Patchy p => p x y -> IO ()
- checkUnrelatedRepos :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> PatchSet p start y -> IO ()
- testTentative :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ExitCode
- testRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ExitCode
- extractOptions :: Repository p r u t -> [DarcsFlag]
- modifyCache :: forall p r u t. RepoPatch p => Repository p r u t -> (Cache -> Cache) -> Repository p r u t
- reportBadSources :: IO ()
- readRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO)
- readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Maybe [SubPath] -> IO (Tree IO)
- unrecordedChanges :: forall p r u t. (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown) -> Repository p r u t -> Maybe [SubPath] -> IO (FL (PrimOf p) t u)
- readPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO, Sealed (FL p t))
- readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO)
- readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO Index
- invalidateIndex :: t -> IO ()
Documentation
data Repository p recordedstate unrecordedstate tentativestate Source
Show (Repository p recordedstate unrecordedstate tentativestate) |
Cache | |
|
RepoJob (forall p r u. (RepoPatch p, ApplyState p ~ Tree, ApplyState (PrimOf p) ~ Tree) => Repository p r u r -> IO a) | |
V1Job (forall r u. Repository (Patch Prim) r u r -> IO a) | |
V2Job (forall r u. Repository (RealPatch Prim) r u r -> IO a) |
maybeIdentifyRepository :: [DarcsFlag] -> String -> IO (IdentifyRepo p r u t)Source
Tries to identify the repository in a given directory
identifyRepositoryFor :: forall p r u t. RepoPatch p => Repository p r u t -> String -> IO (Repository p r u t)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 :: [DarcsFlag] -> RepoJob a -> IO aSource
withRepoReadLock :: [DarcsFlag] -> RepoJob a -> IO aSource
withRepository :: [DarcsFlag] -> RepoJob a -> IO aSource
withGutsOf :: Repository p r u t -> IO a -> IO aSource
makePatchLazy :: RepoPatch p => Repository p r u t -> PatchInfoAnd p x y -> IO (PatchInfoAnd p x y)Source
writePatchSet :: (RepoPatch p, ApplyState p ~ Tree) => PatchSet p Origin x -> [DarcsFlag] -> IO (Repository p r u t)Source
writePatchSet is like patchSetToRepository, except that it doesn't touch the working directory or pristine cache.
replacePristine :: Repository p r u t -> Tree IO -> IO ()Source
Replace the existing pristine with a new one (loaded up in a Tree object).
withRecorded :: RepoPatch p => Repository p r u t -> ((AbsolutePath -> IO a) -> IO a) -> (AbsolutePath -> IO a) -> IO aSource
readRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin r)Source
prefsUrl :: Repository p r u t -> StringSource
readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> IO (PatchSet p Origin t)Source
addToPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) u y -> IO ()Source
tentativelyAddPatch :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> PatchInfoAnd p t y -> IO (Repository p r u y)Source
tentativelyRemovePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u x)Source
tentativelyAddToPending :: forall p r u t x y. RepoPatch p => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) x y -> 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 r u t x. (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Compression -> FL (PatchInfoAnd p) x t -> IO (Repository p r u t)Source
readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin t)Source
tentativelyMergePatches :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u))Source
considerMergeToWorking :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> String -> [DarcsFlag] -> FL (PatchInfoAnd p) x t -> FL (PatchInfoAnd p) x y -> IO (Sealed (FL (PrimOf p) u))Source
revertRepositoryChanges :: RepoPatch p => Repository p r u t -> IO ()Source
finalizeRepositoryChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ()Source
createRepository :: [DarcsFlag] -> IO ()Source
copyRepository :: forall p r u t. (RepoPatch p, ApplyState (PrimOf p) ~ Tree, ApplyState p ~ Tree) => Repository p r u t -> Bool -> IO ()Source
patchSetToRepository :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r1 u1 r1 -> PatchSet p Origin x -> [DarcsFlag] -> IO (Repository p r u t)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 DarcsFlag
s tell
darcs to create a hashed repository, this function will call error
.
unrevertUrl :: Repository p r u t -> StringSource
applyToWorking :: (ApplyState (PrimOf p) ~ Tree, RepoPatch p) => Repository p r u t -> [DarcsFlag] -> FL (PrimOf p) u y -> IO (Repository p r y t)Source
createPristineDirectoryTree :: RepoPatch p => Repository p r u t -> FilePath -> IO ()Source
createPartialsPristineDirectoryTree :: (FilePathLike fp, RepoPatch p) => Repository p r u t -> [fp] -> FilePath -> IO ()Source
Used by the commands dist and diff
optimizeInventory :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> 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 r u t -> IO ()Source
type SealedPatchSet p start = Sealed (PatchSet p start)Source
data PatchInfoAnd p a b Source
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.
PatchInfoAnd
p a b
PatchListFormat (PatchInfoAnd p) | |
(Commute p, MyEq p) => MyEq (PatchInfoAnd p) | |
Commute p => Commute (PatchInfoAnd p) | |
(Commute p, Invert p) => Invert (PatchInfoAnd p) | |
Merge p => Merge (PatchInfoAnd p) | |
PatchInspect p => PatchInspect (PatchInfoAnd p) | |
(ReadPatch p, PatchListFormat p) => ReadPatch (PatchInfoAnd p) | |
Apply p => Apply (PatchInfoAnd p) | |
RepairToFL p => Repair (PatchInfoAnd p) | |
(Apply p, Conflict p, CommuteNoConflicts p, IsHunk p, PatchListFormat p, PrimPatchBase p, ShowPatch p, ~ ((* -> *) -> *) (ApplyState p) Tree) => ShowPatch (PatchInfoAnd p) | |
(PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (PatchInfoAnd p) | |
(RepoPatch p, ~ ((* -> *) -> *) (ApplyState p) Tree) => Patchy (PatchInfoAnd p) | |
IsHunk (PatchInfoAnd p) | |
PrimPatchBase p => PrimPatchBase (PatchInfoAnd p) | |
Effect p => Effect (PatchInfoAnd p) |
setScriptsExecutablePatches :: Patchy p => p x y -> IO ()Source
checkUnrelatedRepos :: RepoPatch p => [DarcsFlag] -> PatchSet p start x -> PatchSet p start y -> IO ()Source
testTentative :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ExitCodeSource
testRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ExitCodeSource
extractOptions :: Repository p r u t -> [DarcsFlag]Source
modifyCache :: forall p r u t. RepoPatch p => Repository p r u t -> (Cache -> Cache) -> Repository p r u tSource
modifyCache
repository function
modifies the cache of
repository
with function
, remove duplicates and sort the results with compareByLocality
.
reportBadSources :: IO ()Source
Prints an error message with a list of bad caches.
Recorded and unrecorded and pending.
readRecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> 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.
Handles the plain and hashed pristine cases. Currently does not handle the
no-pristine case, as that requires replaying patches. Cf. readDarcsHashed
and readPlainTree
in hashed-storage that are used to do the actual Tree
construction.
readUnrecorded :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> Maybe [SubPath] -> IO (Tree IO)Source
Obtains a Tree corresponding to the unrecorded state of the repository: 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 :: forall p r u t. (RepoPatch p, ApplyState p ~ Tree) => (UseIndex, ScanKnown) -> Repository p r u t -> Maybe [SubPath] -> IO (FL (PrimOf p) t u)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 copy + 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: with LookForAdds, we will include any non-boring files (i.e. also those that do not exist in the recorded state) in the working in the unrecorded state, and therefore they will show up in the patches as addfiles.
The IgnoreTimes option 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).
readPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO, Sealed (FL p t))Source
readRecordedAndPending :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (Tree IO)Source
Index.
readIndex :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO IndexSource
invalidateIndex :: t -> IO ()Source
Mark the existing index as invalid. This has to be called whenever the listing of pristine changes and will cause darcs to update the index next time it tries to read it. (NB. This is about files added and removed from pristine: changes to file content in either pristine or working are handled transparently by the index reading code.)