Safe Haskell | None |
---|---|
Language | Haskell2010 |
Darcs.UI.Commands.Pull
Contents
Synopsis
- pull :: DarcsCommand [DarcsFlag]
- fetch :: DarcsCommand [DarcsFlag]
- pullCmd :: PatchApplier pa => pa -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
- data StandardPatchApplier
- fetchPatches :: forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => AbsolutePath -> [DarcsFlag] -> [String] -> String -> Repository rt p wR wU wR -> IO (SealedPatchSet rt p Origin, Sealed ((FL (PatchInfoAnd rt p) :\/: FL (PatchInfoAnd rt p)) wR))
- revertable :: IO a -> IO a
Commands.
pull :: DarcsCommand [DarcsFlag] Source #
fetch :: DarcsCommand [DarcsFlag] Source #
pullCmd :: PatchApplier pa => pa -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO () Source #
data StandardPatchApplier Source #
Instances
PatchApplier StandardPatchApplier Source # | |
Defined in Darcs.UI.ApplyPatches Associated Types type ApplierRepoTypeConstraint StandardPatchApplier rt :: Constraint Source # Methods repoJob :: StandardPatchApplier -> [DarcsFlag] -> (forall (rt :: RepoType) (p :: Type -> Type -> Type) wR wU. (IsRepoType rt, ApplierRepoTypeConstraint StandardPatchApplier rt, RepoPatch p, ApplyState p ~ Tree) => PatchProxy p -> Repository rt p wR wU wR -> IO ()) -> RepoJob () Source # applyPatches :: (ApplierRepoTypeConstraint StandardPatchApplier rt, IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => StandardPatchApplier -> PatchProxy p -> String -> [DarcsFlag] -> String -> Repository rt p wR wU wT -> FL (PatchInfoAnd rt p) wX wT -> FL (PatchInfoAnd rt p) wX wZ -> IO () Source # | |
type ApplierRepoTypeConstraint StandardPatchApplier rt Source # | |
Defined in Darcs.UI.ApplyPatches |
Utility functions.
fetchPatches :: forall rt p wR wU. (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) => AbsolutePath -> [DarcsFlag] -> [String] -> String -> Repository rt p wR wU wR -> IO (SealedPatchSet rt p Origin, Sealed ((FL (PatchInfoAnd rt p) :\/: FL (PatchInfoAnd rt p)) wR)) Source #
revertable :: IO a -> IO a Source #