module Darcs.UI.Commands.Pull (
pull, fetch,
pullCmd, StandardPatchApplier,
fetchPatches, revertable
) where
import Prelude ()
import Darcs.Prelude
import System.Exit ( exitSuccess )
import Control.Monad ( when, unless, (>=>) )
import Data.List ( nub )
import Data.Maybe ( fromMaybe )
import Darcs.UI.Commands
( DarcsCommand(..)
, withStdOpts
, putInfo
, putVerbose
, setEnvDarcsPatches
, defaultRepo
, amInHashedRepository
)
import Darcs.UI.Flags
( DarcsFlag
, fixUrl, getOutput
, changesReverse, verbosity, dryRun, umask, useCache, selectDeps
, remoteRepos, reorder, setDefault
, withContext, hasXmlOutput
, isInteractive, quiet
)
import Darcs.UI.Options ( (^), odesc, ocheck, onormalise, defaultFlags, parseFlags, (?) )
import qualified Darcs.UI.Options.All as O
import Darcs.Repository.Flags ( UpdateWorking (..) )
import Darcs.Repository
( Repository
, identifyRepositoryFor
, withRepoLock
, RepoJob(..)
, readRepo
, modifyCache
, modifyCache
, Cache(..)
, CacheLoc(..)
, WritableOrNot(..)
, filterOutConflicts
)
import qualified Darcs.Repository.Cache as DarcsCache
import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, info, hopefully, patchDesc )
import Darcs.Patch ( IsRepoType, RepoPatch, description )
import Darcs.Patch.Bundle( makeBundleN, patchFilename )
import Darcs.Patch.Apply( ApplyState )
import Darcs.Patch.Set ( Origin, PatchSet(..), SealedPatchSet )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..), seal )
import Darcs.Patch.Witnesses.Unsafe ( unsafeCoercePEnd )
import Darcs.Patch.Witnesses.Ordered
( (:>)(..), (:\/:)(..), FL(..), RL(..)
, mapFL, nullFL, reverseFL, mapFL_FL )
import Darcs.Patch.Permutations ( partitionFL )
import Darcs.Repository.Prefs ( addToPreflist, addRepoSource, getPreflist, showMotd )
import Darcs.Patch.Depends ( findUncommon, findCommonWithThem,
patchSetIntersection, patchSetUnion )
import Darcs.UI.ApplyPatches ( PatchApplier(..), StandardPatchApplier(..) )
import Darcs.UI.Completion ( prefArgs )
import Darcs.UI.Commands.Util ( checkUnrelatedRepos )
import Darcs.UI.SelectChanges
( WhichChanges(..)
, runSelection
, selectionContext
)
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions (..) )
import Darcs.Util.Exception ( clarifyErrors )
import Darcs.Util.Printer ( vcat, ($$), text, putDoc )
import Darcs.Util.Lock ( writeDocBinFile )
import Darcs.Util.Path ( useAbsoluteOrStd, stdOut, AbsolutePath )
import Darcs.Util.Workaround ( getCurrentDirectory )
import Darcs.Util.Text ( quote )
import Darcs.Util.Tree( Tree )
pullDescription :: String
pullDescription =
"Copy and apply patches from another repository to this one."
fetchDescription :: String
fetchDescription =
"Fetch patches from another repository, but don't apply them."
pullHelp :: String
pullHelp = unlines
[ "Pull is used to bring patches made in another repository into the current"
, "repository (that is, either the one in the current directory, or the one"
, "specified with the `--repodir` option). Pull accepts arguments, which are"
, "URLs from which to pull, and when called without an argument, pull will"
, "use the repository specified at `_darcs/prefs/defaultrepo`."
, ""
, "The default (`--union`) behavior is to pull any patches that are in any of"
, "the specified repositories. If you specify the `--intersection` flag, darcs"
, "will only pull those patches which are present in all source repositories."
, "If you specify the `--complement` flag, darcs will only pull elements in the"
, "first repository that do not exist in any of the remaining repositories."
, ""
, "If `--reorder` is supplied, the set of patches that exist only in the current"
, "repository is brought at the top of the current history. This will work even"
, "if there are no new patches to pull."
, ""
, "See `darcs help apply` for detailed description of many options."
]
fetchHelp :: String
fetchHelp = unlines
[ "Fetch is similar to `pull` except that it does not apply any patches"
, "to the current repository. Instead, it generates a patch bundle that"
, "you can apply later with `apply`."
, ""
, "Fetch's behaviour is essentially similar to pull's, so please consult"
, "the help of `pull` to know more."
]
fetch :: DarcsCommand [DarcsFlag]
fetch = DarcsCommand
{ commandProgramName = "darcs"
, commandName = "fetch"
, commandHelp = fetchHelp
, commandDescription = fetchDescription
, commandExtraArgs = 1
, commandExtraArgHelp = ["[REPOSITORY]..."]
, commandCommand = fetchCmd
, commandPrereq = amInHashedRepository
, commandCompleteArgs = prefArgs "repos"
, commandArgdefaults = defaultRepo
, commandAdvancedOptions = odesc advancedOpts
, commandBasicOptions = odesc basicOpts
, commandDefaults = defaultFlags allOpts
, commandCheckOptions = ocheck allOpts
, commandParseOptions = onormalise allOpts
}
where
basicOpts
= O.matchSeveral
^ O.interactive
^ O.dryRun
^ O.summary
^ O.selectDeps
^ O.setDefault
^ O.repoDir
^ O.output
^ O.allowUnrelatedRepos
^ O.diffAlgorithm
advancedOpts
= O.repoCombinator
^ O.remoteRepos
^ O.network
allOpts = basicOpts `withStdOpts` advancedOpts
pull :: DarcsCommand [DarcsFlag]
pull = DarcsCommand
{ commandProgramName = "darcs"
, commandName = "pull"
, commandHelp = pullHelp
, commandDescription = pullDescription
, commandExtraArgs = 1
, commandExtraArgHelp = ["[REPOSITORY]..."]
, commandCommand = pullCmd StandardPatchApplier
, commandPrereq = amInHashedRepository
, commandCompleteArgs = prefArgs "repos"
, commandArgdefaults = defaultRepo
, commandAdvancedOptions = odesc advancedOpts
, commandBasicOptions = odesc basicOpts
, commandDefaults = defaultFlags allOpts
, commandCheckOptions = ocheck allOpts
, commandParseOptions = onormalise allOpts
}
where
basicOpts
= O.matchSeveral
^ O.reorder
^ O.interactive
^ O.conflictsYes
^ O.externalMerge
^ O.runTest
^ O.dryRunXml
^ O.summary
^ O.selectDeps
^ O.setDefault
^ O.repoDir
^ O.allowUnrelatedRepos
^ O.diffAlgorithm
advancedOpts
= O.repoCombinator
^ O.compress
^ O.useIndex
^ O.remoteRepos
^ O.setScriptsExecutable
^ O.umask
^ O.restrictPaths
^ O.changesReverse
^ O.pauseForGui
^ O.network
allOpts = basicOpts `withStdOpts` advancedOpts
pullCmd
:: PatchApplier pa
=> pa -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
pullCmd patchApplier (_,o) opts repos =
do
pullingFrom <- mapM (fixUrl o) repos
withRepoLock (dryRun ? opts) (useCache ? opts) YesUpdateWorking (umask ? opts) $
repoJob patchApplier opts $ \patchProxy initRepo -> do
let repository = modifyCache initRepo $ addReposToCache pullingFrom
(_, Sealed (us' :\/: to_be_pulled))
<- fetchPatches o opts repos "pull" repository
let from_whom = error "Internal error: pull shouldn't need a 'from' address"
applyPatches patchApplier patchProxy "pull" opts from_whom repository us' to_be_pulled
where
addReposToCache repos' (Ca cache) = Ca $ [ toReadOnlyCache r | r <- repos' ] ++ cache
toReadOnlyCache = Cache DarcsCache.Repo NotWritable
fetchCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
fetchCmd (_,o) opts repos =
withRepoLock (dryRun ? opts) (useCache ? opts) YesUpdateWorking (umask ? opts) $ RepoJob $
fetchPatches o opts repos "fetch" >=> makeBundle opts
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))
fetchPatches o opts unfixedrepodirs@(_:_) jobname repository = do
here <- getCurrentDirectory
repodirs <- (nub . filter (/= here)) `fmap` mapM (fixUrl o) unfixedrepodirs
when (null repodirs) $
fail "Can't pull from current repository!"
old_default <- getPreflist "defaultrepo"
when (old_default == repodirs && not (hasXmlOutput opts)) $
let pulling = case dryRun ? opts of
O.YesDryRun -> "Would pull"
O.NoDryRun -> "Pulling"
in putInfo opts $ text $ pulling++" from "++concatMap quote repodirs++"..."
(Sealed them, Sealed compl) <- readRepos repository opts repodirs
addRepoSource (head repodirs) (dryRun ? opts) (remoteRepos ? opts) (setDefault False opts)
mapM_ (addToPreflist "repos") repodirs
unless (quiet opts || hasXmlOutput opts) $ mapM_ showMotd repodirs
us <- readRepo repository
checkUnrelatedRepos (parseFlags O.allowUnrelatedRepos opts) us them
common :> _ <- return $ findCommonWithThem us them
us' :\/: them' <- return $ findUncommon us them
_ :\/: compl' <- return $ findUncommon us compl
let avoided = mapFL info compl'
ps :> _ <- return $ partitionFL (not . (`elem` avoided) . info) them'
putVerbose opts $
case us' of
(x@(_ :>: _)) ->
text "We have the following new (to them) patches:" $$
vcat (mapFL description x)
_ -> mempty
unless (nullFL ps) $ putVerbose opts $
text "They have the following patches to pull:" $$
vcat (mapFL description ps)
(hadConflicts, Sealed psFiltered)
<- if O.conflictsYes ? opts == Nothing
then filterOutConflicts (reverseFL us') repository ps
else return (False, Sealed ps)
when hadConflicts $ putInfo opts $ text "Skipping some patches which would cause conflicts."
when (nullFL psFiltered) $ do putInfo opts $ text "No remote patches to pull in!"
setEnvDarcsPatches psFiltered
when (reorder ? opts /= O.Reorder) exitSuccess
let direction = if changesReverse ? opts then FirstReversed else First
context = selectionContext direction jobname (pullPatchSelOpts opts) Nothing Nothing
(to_be_pulled :> _) <- runSelection psFiltered context
return (seal common, seal $ us' :\/: to_be_pulled)
fetchPatches _ _ [] jobname _ = fail $
"No default repository to " ++ jobname ++ " from, please specify one"
makeBundle :: forall rt p wR . (RepoPatch p, ApplyState p ~ Tree)
=> [DarcsFlag]
-> (SealedPatchSet rt p Origin,
Sealed ((FL (PatchInfoAnd rt p) :\/: FL (PatchInfoAnd rt p)) wR))
-> IO ()
makeBundle opts (Sealed common, Sealed (_ :\/: to_be_fetched)) =
do
bundle <- makeBundleN Nothing (unsafeCoercePEnd common) $
mapFL_FL hopefully to_be_fetched
let fname = case to_be_fetched of
(x:>:_)-> patchFilename $ patchDesc x
_ -> impossible
o = fromMaybe stdOut (getOutput opts fname)
useAbsoluteOrStd writeDocBinFile putDoc o bundle
revertable :: IO a -> IO a
revertable x =
x `clarifyErrors` unlines
["Error applying patch to the working directory.","",
"This may have left your working directory an inconsistent",
"but recoverable state. If you had no un-recorded changes",
"by using 'darcs revert' you should be able to make your",
"working directory consistent again."]
readRepos :: (IsRepoType rt, RepoPatch p)
=> Repository rt p wR wU wT -> [DarcsFlag] -> [String]
-> IO (SealedPatchSet rt p Origin,SealedPatchSet rt p Origin)
readRepos _ _ [] = impossible
readRepos to_repo opts us =
do rs <- mapM (\u -> do r <- identifyRepositoryFor to_repo (useCache ? opts) u
ps <- readRepo r
return $ seal ps) us
return $ case parseFlags O.repoCombinator opts of
O.Intersection -> (patchSetIntersection rs, seal (PatchSet NilRL NilRL))
O.Complement -> (head rs, patchSetUnion $ tail rs)
O.Union -> (patchSetUnion rs, seal (PatchSet NilRL NilRL))
pullPatchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
pullPatchSelOpts flags = S.PatchSelectionOptions
{ S.verbosity = verbosity ? flags
, S.matchFlags = parseFlags O.matchSeveral flags
, S.interactive = isInteractive True flags
, S.selectDeps = selectDeps ? flags
, S.summary = O.summary ? flags
, S.withContext = withContext ? flags
}