Safe Haskell | Safe-Infered |
---|
- data Repository p recordedstate unrecordedstate tentativestate = Repo !String ![DarcsFlag] !RepoFormat !(RepoType p)
- data RepoType p = DarcsRepository !Pristine Cache
- data RIO p r u t t1 a
- 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)
- identifyDarcsRepository :: forall p r u t. [DarcsFlag] -> String -> IO (Repository p r u t)
- identifyRepositoryFor :: forall p r u t. RepoPatch p => Repository p r u t -> String -> IO (Repository p r u t)
- data IdentifyRepo p r u t
- = BadRepository String
- | NonRepository String
- | GoodRepository (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 ())
- revertRepositoryChanges :: RepoPatch p => Repository p r u t -> IO ()
- announceMergeConflicts :: (PrimPatch p, PatchInspect p) => String -> [DarcsFlag] -> FL p x y -> IO Bool
- setTentativePending :: forall p r u t x y. RepoPatch p => Repository p r u t -> FL (PrimOf p) x y -> IO ()
- checkUnrecordedConflicts :: forall p t y. RepoPatch p => [DarcsFlag] -> FL (Named p) t y -> IO Bool
- 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)
- readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin t)
- readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> IO (PatchSet p Origin t)
- prefsUrl :: Repository p r u t -> String
- makePatchLazy :: RepoPatch p => Repository p r u t -> PatchInfoAnd p x y -> IO (PatchInfoAnd p x y)
- 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
- 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 ()
- tentativelyAddPatch_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository p r u t -> Compression -> PatchInfoAnd p t y -> IO (Repository p r u y)
- 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)
- finalizeRepositoryChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ()
- 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 ()
- setScriptsExecutable :: IO ()
- setScriptsExecutablePatches :: Patchy p => p x y -> IO ()
- getRepository :: RIO p r u t t (Repository p r u t)
- rIO :: IO a -> RIO p r u t t a
- 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
- data UpdatePristine
- data MakeChanges
- applyToTentativePristine :: (ApplyState q ~ Tree, Effect q, Patchy q, PrimPatchBase q) => Repository p r u t -> q t y -> IO ()
- makeNewPending :: forall p r u t y. (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) t y -> IO ()
- seekRepo :: IO (Maybe (Either String ()))
Documentation
data Repository p recordedstate unrecordedstate tentativestate Source
Repo !String ![DarcsFlag] !RepoFormat !(RepoType p) |
Show (Repository p recordedstate unrecordedstate tentativestate) |
Repository IO monad. This monad-like datatype is responsible for sequencing IO actions that modify the tentative recorded state of the repository.
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
identifyDarcsRepository :: forall p r u t. [DarcsFlag] -> String -> IO (Repository p r u t)Source
identifyDarcsRepository identifies the repo at url
. Warning:
you have to know what kind of patches are found in that repo.
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.
data IdentifyRepo p r u t Source
The status of a given directory: is it a darcs repository?
BadRepository String | looks like a repository with some error |
NonRepository String | safest guess |
GoodRepository (Repository p r u t) |
revertRepositoryChanges :: RepoPatch p => Repository p r u t -> IO ()Source
announceMergeConflicts :: (PrimPatch p, PatchInspect p) => String -> [DarcsFlag] -> FL p x y -> IO BoolSource
setTentativePending :: forall p r u t x y. RepoPatch p => Repository p r u t -> FL (PrimOf p) x y -> IO ()Source
setTentativePending is basically unsafe. It overwrites the pending state with a new one, not related to the repository state.
checkUnrecordedConflicts :: forall p t y. RepoPatch p => [DarcsFlag] -> FL (Named p) t y -> IO BoolSource
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
readTentativeRepo :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO (PatchSet p Origin t)Source
readRepoUsingSpecificInventory :: (RepoPatch p, ApplyState p ~ Tree) => String -> Repository p r u t -> IO (PatchSet p Origin t)Source
prefsUrl :: Repository p r u t -> StringSource
makePatchLazy :: RepoPatch p => Repository p r u t -> PatchInfoAnd p x y -> IO (PatchInfoAnd p x y)Source
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
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.
tentativelyAddPatch_ :: (RepoPatch p, ApplyState p ~ Tree) => UpdatePristine -> Repository p r u t -> Compression -> PatchInfoAnd p t y -> IO (Repository p r u y)Source
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
finalizeRepositoryChanges :: (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> IO ()Source
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
setScriptsExecutablePatches :: Patchy p => p x y -> IO ()Source
getRepository :: RIO p r u t t (Repository p r u t)Source
Similar to the ask
function of the MonadReader class.
This allows actions in the RIO monad to get the current
repository.
FIXME: Don't export this. If we don't export this
it makes it harder for arbitrary IO actions to access
the repository and hence our code is easier to audit.
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
applyToTentativePristine :: (ApplyState q ~ Tree, Effect q, Patchy q, PrimPatchBase q) => Repository p r u t -> q t y -> IO ()Source
makeNewPending :: forall p r u t y. (RepoPatch p, ApplyState p ~ Tree) => Repository p r u t -> FL (PrimOf p) t y -> IO ()Source
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