{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.Commands.Pull (
pull, fetch,
pullCmd, StandardPatchApplier,
fetchPatches
) where
import Darcs.Prelude
import System.Exit ( exitSuccess )
import Control.Monad ( when, unless, (>=>) )
import Data.List ( nub )
import Data.Maybe ( fromMaybe )
import Safe ( headErr, tailErr )
import Darcs.UI.Commands
( DarcsCommand(..)
, withStdOpts
, putInfo
, putVerbose
, setEnvDarcsPatches
, defaultRepo
, amInHashedRepository
)
import Darcs.UI.Commands.Clone ( otherHelpInheritDefault )
import Darcs.UI.Flags
( DarcsFlag
, fixUrl, getOutput
, changesReverse, verbosity, dryRun, umask, useCache, selectDeps
, reorder, setDefault
, hasXmlOutput
, isInteractive, quiet
)
import Darcs.UI.Options ( parseFlags, (?), (^) )
import qualified Darcs.UI.Options.All as O
import Darcs.Repository
( Repository
, AccessType(..)
, identifyRepositoryFor
, ReadingOrWriting(..)
, withRepoLock
, RepoJob(..)
, readPatches
, modifyCache
, mkCache
, cacheEntries
, CacheLoc(..)
, WritableOrNot(..)
, CacheType(..)
, filterOutConflicts
)
import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, info, hopefully, patchDesc )
import Darcs.Patch ( RepoPatch, description )
import qualified Darcs.Patch.Bundle as Bundle ( makeBundle )
import Darcs.Patch.Apply( ApplyState )
import Darcs.Patch.Set ( PatchSet, Origin, emptyPatchSet, SealedPatchSet )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..), seal )
import Darcs.Patch.Witnesses.Ordered
( (:>)(..), FL(..), Fork(..)
, mapFL, nullFL, mapFL_FL )
import Darcs.Patch.Permutations ( partitionFL )
import Darcs.Repository.Prefs
( Pref(Defaultrepo, Repos)
, addRepoSource
, addToPreflist
, getPreflist
, showMotd
)
import Darcs.Patch.Depends
( findCommon
, findCommonWithThem
, patchSetIntersection
, patchSetUnion
)
import Darcs.UI.ApplyPatches ( PatchApplier(..), StandardPatchApplier(..) )
import Darcs.UI.Completion ( prefArgs )
import Darcs.UI.Commands.Util ( checkUnrelatedRepos, getUniqueDPatchName )
import Darcs.UI.SelectChanges
( WhichChanges(..)
, runSelection
, selectionConfig
)
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions (..) )
import Darcs.Util.Printer
( Doc
, ($$)
, ($+$)
, (<+>)
, formatWords
, hsep
, putDoc
, quoted
, text
, vcat
)
import Darcs.Util.Lock ( writeDocBinFile )
import Darcs.Util.Path ( useAbsoluteOrStd, stdOut, AbsolutePath )
import Darcs.Util.Workaround ( getCurrentDirectory )
import Darcs.Util.Tree( Tree )
pullDescription :: String
pullDescription :: String
pullDescription =
String
"Copy and apply patches from another repository to this one."
fetchDescription :: String
fetchDescription :: String
fetchDescription =
String
"Fetch patches from another repository, but don't apply them."
pullHelp :: Doc
pullHelp :: Doc
pullHelp =
[String] -> Doc
formatWords
[ String
"Pull is used to bring patches made in another repository into the current"
, String
"repository (that is, either the one in the current directory, or the one"
, String
"specified with the `--repodir` option). Pull accepts arguments, which are"
, String
"URLs from which to pull, and when called without an argument, pull will"
, String
"use the repository specified at `_darcs/prefs/defaultrepo`."
]
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"The default (`--union`) behavior is to pull any patches that are in any of"
, String
"the specified repositories. If you specify the `--intersection` flag, darcs"
, String
"will only pull those patches which are present in all source repositories."
, String
"If you specify the `--complement` flag, darcs will only pull elements in the"
, String
"first repository that do not exist in any of the remaining repositories."
]
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"If `--reorder` is supplied, the set of patches that exist only in the current"
, String
"repository is brought at the top of the current history. This will work even"
, String
"if there are no new patches to pull."
]
Doc -> Doc -> Doc
$+$ Doc
otherHelpInheritDefault
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"See `darcs help apply` for detailed description of many options."
]
fetchHelp :: Doc
fetchHelp :: Doc
fetchHelp =
[String] -> Doc
formatWords
[ String
"Fetch is similar to `pull` except that it does not apply any patches"
, String
"to the current repository. Instead, it generates a patch bundle that"
, String
"you can apply later with `apply`."
]
Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
[ String
"Fetch's behaviour is essentially similar to pull's, so please consult"
, String
"the help of `pull` to know more."
]
fetch :: DarcsCommand
fetch :: DarcsCommand
fetch = DarcsCommand
{ commandProgramName :: String
commandProgramName = String
"darcs"
, commandName :: String
commandName = String
"fetch"
, commandHelp :: Doc
commandHelp = Doc
fetchHelp
, commandDescription :: String
commandDescription = String
fetchDescription
, commandExtraArgs :: Int
commandExtraArgs = -Int
1
, commandExtraArgHelp :: [String]
commandExtraArgHelp = [String
"[REPOSITORY]..."]
, commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
commandCommand = (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
fetchCmd
, commandPrereq :: [DarcsFlag] -> IO (Either String ())
commandPrereq = [DarcsFlag] -> IO (Either String ())
amInHashedRepository
, commandCompleteArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
commandCompleteArgs = Pref
-> (AbsolutePath, AbsolutePath)
-> [DarcsFlag]
-> [String]
-> IO [String]
prefArgs Pref
Repos
, commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
defaultRepo
, commandOptions :: CommandOptions
commandOptions = CommandOptions
allOpts
}
where
basicOpts :: OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
basicOpts
= PrimOptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
[MatchFlag]
MatchOption
O.matchSeveral
PrimOptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
[MatchFlag]
-> OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption (Maybe Bool)
O.interactive
OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption DryRun
O.dryRun
OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption WithSummary
O.withSummary
OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption SelectDeps
O.selectDeps
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault
-> Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
(Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault
-> Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault
-> Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
(Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption (Maybe Bool)
O.setDefault
OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault
-> Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
(InheritDefault
-> Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
(InheritDefault
-> Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
PrimDarcsOption InheritDefault
O.inheritDefault
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Output -> Bool -> DiffAlgorithm -> a)
(Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Output -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Output -> Bool -> DiffAlgorithm -> a)
(Maybe String -> Maybe Output -> Bool -> DiffAlgorithm -> a)
PrimDarcsOption (Maybe String)
O.repoDir
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Output -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
(Maybe Output -> Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
(Maybe Output -> Bool -> DiffAlgorithm -> a)
PrimDarcsOption (Maybe Output)
O.output
OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
(Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
(Bool -> DiffAlgorithm -> a)
PrimDarcsOption Bool
O.allowUnrelatedRepos
OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec DarcsOptDescr DarcsFlag a (DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr DarcsFlag a (DiffAlgorithm -> a)
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm
advancedOpts :: OptSpec
DarcsOptDescr DarcsFlag a (RepoCombinator -> RemoteDarcs -> a)
advancedOpts
= PrimOptSpec
DarcsOptDescr DarcsFlag (RemoteDarcs -> a) RepoCombinator
PrimDarcsOption RepoCombinator
O.repoCombinator
PrimOptSpec
DarcsOptDescr DarcsFlag (RemoteDarcs -> a) RepoCombinator
-> OptSpec DarcsOptDescr DarcsFlag a (RemoteDarcs -> a)
-> OptSpec
DarcsOptDescr DarcsFlag a (RepoCombinator -> RemoteDarcs -> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr DarcsFlag a (RemoteDarcs -> a)
PrimDarcsOption RemoteDarcs
O.remoteDarcs
allOpts :: CommandOptions
allOpts = OptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
forall {a}.
OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> a)
basicOpts OptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
([MatchFlag]
-> Maybe Bool
-> DryRun
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Maybe Output
-> Bool
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(RepoCombinator
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
-> CommandOptions
forall b c.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
b
-> CommandOptions
`withStdOpts` DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(RepoCombinator
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
forall {a}.
OptSpec
DarcsOptDescr DarcsFlag a (RepoCombinator -> RemoteDarcs -> a)
advancedOpts
pull :: DarcsCommand
pull :: DarcsCommand
pull = DarcsCommand
{ commandProgramName :: String
commandProgramName = String
"darcs"
, commandName :: String
commandName = String
"pull"
, commandHelp :: Doc
commandHelp = Doc
pullHelp
, commandDescription :: String
commandDescription = String
pullDescription
, commandExtraArgs :: Int
commandExtraArgs = -Int
1
, commandExtraArgHelp :: [String]
commandExtraArgHelp = [String
"[REPOSITORY]..."]
, commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
commandCommand = StandardPatchApplier
-> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
forall pa.
PatchApplier pa =>
pa
-> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
pullCmd StandardPatchApplier
StandardPatchApplier
, commandPrereq :: [DarcsFlag] -> IO (Either String ())
commandPrereq = [DarcsFlag] -> IO (Either String ())
amInHashedRepository
, commandCompleteArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
commandCompleteArgs = Pref
-> (AbsolutePath, AbsolutePath)
-> [DarcsFlag]
-> [String]
-> IO [String]
prefArgs Pref
Repos
, commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
defaultRepo
, commandOptions :: CommandOptions
commandOptions = CommandOptions
allOpts
}
where
basicOpts :: OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
basicOpts
= PrimOptSpec
DarcsOptDescr
DarcsFlag
(Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
[MatchFlag]
MatchOption
O.matchSeveral
PrimOptSpec
DarcsOptDescr
DarcsFlag
(Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
[MatchFlag]
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption Reorder
O.reorder
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption (Maybe Bool)
O.interactive
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption (Maybe AllowConflicts)
O.conflictsYes
OptSpec
DarcsOptDescr
DarcsFlag
(TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption TestChanges
O.testChanges
OptSpec
DarcsOptDescr
DarcsFlag
(DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall a. DarcsOption a (DryRun -> XmlOutput -> a)
O.dryRunXml
OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
(WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption WithSummary
O.withSummary
OptSpec
DarcsOptDescr
DarcsFlag
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
(SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
PrimDarcsOption SelectDeps
O.selectDeps
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool
-> InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
(Maybe Bool
-> InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
(Maybe Bool
-> InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
PrimDarcsOption (Maybe Bool)
O.setDefault
OptSpec
DarcsOptDescr
DarcsFlag
(InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Bool -> DiffAlgorithm -> a)
(InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Bool -> DiffAlgorithm -> a)
(InheritDefault -> Maybe String -> Bool -> DiffAlgorithm -> a)
PrimDarcsOption InheritDefault
O.inheritDefault
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
(Maybe String -> Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
(Maybe String -> Bool -> DiffAlgorithm -> a)
PrimDarcsOption (Maybe String)
O.repoDir
OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
(Bool -> DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
(Bool -> DiffAlgorithm -> a)
PrimDarcsOption Bool
O.allowUnrelatedRepos
OptSpec
DarcsOptDescr
DarcsFlag
(DiffAlgorithm -> a)
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
-> OptSpec DarcsOptDescr DarcsFlag a (DiffAlgorithm -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr DarcsFlag a (DiffAlgorithm -> a)
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm
advancedOpts :: OptSpec
DarcsOptDescr
DarcsFlag
a
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
advancedOpts
= PrimOptSpec
DarcsOptDescr
DarcsFlag
(SetScriptsExecutable
-> UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
RepoCombinator
PrimDarcsOption RepoCombinator
O.repoCombinator
PrimOptSpec
DarcsOptDescr
DarcsFlag
(SetScriptsExecutable
-> UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
RepoCombinator
-> OptSpec
DarcsOptDescr
DarcsFlag
(UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
(SetScriptsExecutable
-> UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
(SetScriptsExecutable
-> UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
PrimDarcsOption SetScriptsExecutable
O.setScriptsExecutable
OptSpec
DarcsOptDescr
DarcsFlag
(UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> WantGuiPause -> RemoteDarcs -> a)
(UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> WantGuiPause -> RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> WantGuiPause -> RemoteDarcs -> a)
(UMask -> Bool -> WantGuiPause -> RemoteDarcs -> a)
PrimDarcsOption UMask
O.umask
OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> WantGuiPause -> RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WantGuiPause -> RemoteDarcs -> a)
(Bool -> WantGuiPause -> RemoteDarcs -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WantGuiPause -> RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(WantGuiPause -> RemoteDarcs -> a)
(Bool -> WantGuiPause -> RemoteDarcs -> a)
PrimDarcsOption Bool
O.changesReverse
OptSpec
DarcsOptDescr
DarcsFlag
(WantGuiPause -> RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(RemoteDarcs -> a)
(WantGuiPause -> RemoteDarcs -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
DarcsOptDescr
DarcsFlag
(RemoteDarcs -> a)
(WantGuiPause -> RemoteDarcs -> a)
PrimDarcsOption WantGuiPause
O.pauseForGui
OptSpec
DarcsOptDescr
DarcsFlag
(RemoteDarcs -> a)
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
-> OptSpec DarcsOptDescr DarcsFlag a (RemoteDarcs -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
a
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec DarcsOptDescr DarcsFlag a (RemoteDarcs -> a)
PrimDarcsOption RemoteDarcs
O.remoteDarcs
allOpts :: CommandOptions
allOpts = OptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
forall {a}.
OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> a)
basicOpts OptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
([MatchFlag]
-> Reorder
-> Maybe Bool
-> Maybe AllowConflicts
-> TestChanges
-> DryRun
-> XmlOutput
-> WithSummary
-> SelectDeps
-> Maybe Bool
-> InheritDefault
-> Maybe String
-> Bool
-> DiffAlgorithm
-> Maybe StdCmdAction
-> Verbosity
-> RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
-> CommandOptions
forall b c.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
b
-> CommandOptions
`withStdOpts` DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
forall {a}.
OptSpec
DarcsOptDescr
DarcsFlag
a
(RepoCombinator
-> SetScriptsExecutable
-> UMask
-> Bool
-> WantGuiPause
-> RemoteDarcs
-> a)
advancedOpts
pullCmd
:: PatchApplier pa
=> pa -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
pullCmd :: forall pa.
PatchApplier pa =>
pa
-> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
pullCmd pa
patchApplier (AbsolutePath
_,AbsolutePath
o) [DarcsFlag]
opts [String]
repos =
do
[String]
pullingFrom <- (String -> IO String) -> [String] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (AbsolutePath -> String -> IO String
fixUrl AbsolutePath
o) [String]
repos
UseCache -> UMask -> RepoJob 'RW () -> IO ()
forall a. UseCache -> UMask -> RepoJob 'RW a -> IO a
withRepoLock (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (PrimOptSpec DarcsOptDescr DarcsFlag a UMask
PrimDarcsOption UMask
umask PrimDarcsOption UMask -> [DarcsFlag] -> UMask
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (RepoJob 'RW () -> IO ()) -> RepoJob 'RW () -> IO ()
forall a b. (a -> b) -> a -> b
$
pa
-> (forall (p :: * -> * -> *) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
PatchProxy p -> Repository 'RW p wU wR -> IO ())
-> RepoJob 'RW ()
forall pa.
PatchApplier pa =>
pa
-> (forall (p :: * -> * -> *) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
PatchProxy p -> Repository 'RW p wU wR -> IO ())
-> RepoJob 'RW ()
repoJob pa
patchApplier ((forall (p :: * -> * -> *) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
PatchProxy p -> Repository 'RW p wU wR -> IO ())
-> RepoJob 'RW ())
-> (forall (p :: * -> * -> *) wR wU.
(RepoPatch p, ApplyState p ~ Tree) =>
PatchProxy p -> Repository 'RW p wU wR -> IO ())
-> RepoJob 'RW ()
forall a b. (a -> b) -> a -> b
$ \PatchProxy p
patchProxy Repository 'RW p wU wR
initRepo -> do
let repository :: Repository 'RW p wU wR
repository = (Cache -> Cache)
-> Repository 'RW p wU wR -> Repository 'RW p wU wR
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
(Cache -> Cache) -> Repository rt p wU wR -> Repository rt p wU wR
modifyCache ([String] -> Cache -> Cache
addReposToCache [String]
pullingFrom) Repository 'RW p wU wR
initRepo
Sealed Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX
fork <- AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository 'RW p wU wR
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository 'RW p wU wR
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
fetchPatches AbsolutePath
o [DarcsFlag]
opts [String]
repos String
"pull" Repository 'RW p wU wR
repository
pa
-> PatchProxy p
-> String
-> [DarcsFlag]
-> Repository 'RW p wU wR
-> Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX
-> IO ()
forall pa (p :: * -> * -> *) wR wU wZ.
(PatchApplier pa, RepoPatch p, ApplyState p ~ Tree) =>
pa
-> PatchProxy p
-> String
-> [DarcsFlag]
-> Repository 'RW p wU wR
-> Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wZ
-> IO ()
forall (p :: * -> * -> *) wR wU wZ.
(RepoPatch p, ApplyState p ~ Tree) =>
pa
-> PatchProxy p
-> String
-> [DarcsFlag]
-> Repository 'RW p wU wR
-> Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wZ
-> IO ()
applyPatches pa
patchApplier PatchProxy p
patchProxy String
"pull" [DarcsFlag]
opts Repository 'RW p wU wR
repository Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX
fork
where
addReposToCache :: [String] -> Cache -> Cache
addReposToCache [String]
repos' Cache
cache =
[CacheLoc] -> Cache
mkCache ([CacheLoc] -> Cache) -> [CacheLoc] -> Cache
forall a b. (a -> b) -> a -> b
$ [ String -> CacheLoc
toReadOnlyCache String
r | String
r <- [String]
repos' ] [CacheLoc] -> [CacheLoc] -> [CacheLoc]
forall a. [a] -> [a] -> [a]
++ Cache -> [CacheLoc]
cacheEntries Cache
cache
toReadOnlyCache :: String -> CacheLoc
toReadOnlyCache = CacheType -> WritableOrNot -> String -> CacheLoc
Cache CacheType
Repo WritableOrNot
NotWritable
fetchCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
fetchCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
fetchCmd (AbsolutePath
_,AbsolutePath
o) [DarcsFlag]
opts [String]
repos =
UseCache -> UMask -> RepoJob 'RW () -> IO ()
forall a. UseCache -> UMask -> RepoJob 'RW a -> IO a
withRepoLock (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (PrimOptSpec DarcsOptDescr DarcsFlag a UMask
PrimDarcsOption UMask
umask PrimDarcsOption UMask -> [DarcsFlag] -> UMask
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (RepoJob 'RW () -> IO ()) -> RepoJob 'RW () -> IO ()
forall a b. (a -> b) -> a -> b
$ TreePatchJob 'RW () -> RepoJob 'RW ()
forall (rt :: AccessType) a. TreePatchJob rt a -> RepoJob rt a
RepoJob (TreePatchJob 'RW () -> RepoJob 'RW ())
-> TreePatchJob 'RW () -> RepoJob 'RW ()
forall a b. (a -> b) -> a -> b
$
AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository 'RW p wU wR
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository 'RW p wU wR
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
fetchPatches AbsolutePath
o [DarcsFlag]
opts [String]
repos String
"fetch" (Repository 'RW p wU wR
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR)))
-> (Sealed
(Fork
(PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR)
-> IO ())
-> Repository 'RW p wU wR
-> IO ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> [DarcsFlag]
-> Sealed
(Fork
(PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR)
-> IO ()
forall (p :: * -> * -> *) wR.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> Sealed
(Fork
(PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR)
-> IO ()
makeBundle [DarcsFlag]
opts
fetchPatches :: (RepoPatch p, ApplyState p ~ Tree)
=> AbsolutePath -> [DarcsFlag] -> [String] -> String
-> Repository 'RW p wU wR
-> IO (Sealed (Fork (PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p)) Origin wR))
fetchPatches :: forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository 'RW p wU wR
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
fetchPatches AbsolutePath
o [DarcsFlag]
opts unfixedrepourls :: [String]
unfixedrepourls@(String
_:[String]
_) String
jobname Repository 'RW p wU wR
repository = do
String
here <- IO String
getCurrentDirectory
[String]
repourls <- ([String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
here)) ([String] -> [String]) -> IO [String] -> IO [String]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (String -> IO String) -> [String] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (AbsolutePath -> String -> IO String
fixUrl AbsolutePath
o) [String]
unfixedrepourls
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
repourls) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Can't pull from current repository!"
[String]
old_default <- Pref -> IO [String]
getPreflist Pref
Defaultrepo
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([String]
old_default [String] -> [String] -> Bool
forall a. Eq a => a -> a -> Bool
== [String]
repourls Bool -> Bool -> Bool
&& Bool -> Bool
not ([DarcsFlag] -> Bool
hasXmlOutput [DarcsFlag]
opts)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
let pulling :: String
pulling = case PrimOptSpec DarcsOptDescr DarcsFlag a DryRun
PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts of
DryRun
O.YesDryRun -> String
"Would pull"
DryRun
O.NoDryRun -> String
"Pulling"
in [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
pulling Doc -> Doc -> Doc
<+> Doc
"from" Doc -> Doc -> Doc
<+> [Doc] -> Doc
hsep ((String -> Doc) -> [String] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
quoted [String]
repourls) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"..."
(Sealed PatchSet p Origin wX
them, Sealed PatchSet p Origin wX
compl) <- Repository 'RW p wU wR
-> [DarcsFlag]
-> [String]
-> IO (SealedPatchSet p Origin, SealedPatchSet p Origin)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR
-> [DarcsFlag]
-> [String]
-> IO (SealedPatchSet p Origin, SealedPatchSet p Origin)
readRepos Repository 'RW p wU wR
repository [DarcsFlag]
opts [String]
repourls
String -> DryRun -> SetDefault -> InheritDefault -> Bool -> IO ()
addRepoSource ([String] -> String
forall a. Partial => [a] -> a
headErr [String]
repourls) (PrimOptSpec DarcsOptDescr DarcsFlag a DryRun
PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
(Bool -> [DarcsFlag] -> SetDefault
setDefault Bool
False [DarcsFlag]
opts) (PrimOptSpec DarcsOptDescr DarcsFlag a InheritDefault
PrimDarcsOption InheritDefault
O.inheritDefault PrimDarcsOption InheritDefault -> [DarcsFlag] -> InheritDefault
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (Bool -> [DarcsFlag] -> Bool
isInteractive Bool
True [DarcsFlag]
opts)
(String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Pref -> String -> IO ()
addToPreflist Pref
Repos) [String]
repourls
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([DarcsFlag] -> Bool
quiet [DarcsFlag]
opts Bool -> Bool -> Bool
|| [DarcsFlag] -> Bool
hasXmlOutput [DarcsFlag]
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> IO ()
showMotd [String]
repourls
PatchSet p Origin wR
us <- Repository 'RW p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RW p wU wR
repository
Bool -> PatchSet p Origin wR -> PatchSet p Origin wX -> IO ()
forall (p :: * -> * -> *) wX wY.
RepoPatch p =>
Bool -> PatchSet p Origin wX -> PatchSet p Origin wY -> IO ()
checkUnrelatedRepos (PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.allowUnrelatedRepos [DarcsFlag]
opts) PatchSet p Origin wR
us PatchSet p Origin wX
them
Fork PatchSet p Origin wU
common FL (PatchInfoAnd p) wU wR
us' FL (PatchInfoAnd p) wU wX
them' <- Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX
-> IO
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX
-> IO
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX))
-> Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX
-> IO
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX)
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin wR
-> PatchSet p Origin wX
-> Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wX
forall (p :: * -> * -> *) wX wY.
Commute p =>
PatchSet p Origin wX
-> PatchSet p Origin wY
-> Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wX
wY
findCommon PatchSet p Origin wR
us PatchSet p Origin wX
them
PatchSet p Origin wZ
_ :> FL (PatchInfoAnd p) wZ wX
compl' <- (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX
-> IO ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX
-> IO ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX))
-> (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX
-> IO ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX)
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin wX
-> PatchSet p Origin wR
-> (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX
forall (p :: * -> * -> *) wX wY.
Commute p =>
PatchSet p Origin wX
-> PatchSet p Origin wY
-> (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX
findCommonWithThem PatchSet p Origin wX
compl PatchSet p Origin wR
us
let avoided :: [PatchInfo]
avoided = (forall wW wZ. PatchInfoAnd p wW wZ -> PatchInfo)
-> FL (PatchInfoAnd p) wZ wX -> [PatchInfo]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL PatchInfoAndG (Named p) wW wZ -> PatchInfo
forall wW wZ. PatchInfoAnd p wW wZ -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info FL (PatchInfoAnd p) wZ wX
compl'
FL (PatchInfoAnd p) wU wZ
ps :> (:>) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) wZ wX
_ <- (:>)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p) :> FL (PatchInfoAnd p))
wU
wX
-> IO
((:>)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p) :> FL (PatchInfoAnd p))
wU
wX)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((:>)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p) :> FL (PatchInfoAnd p))
wU
wX
-> IO
((:>)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p) :> FL (PatchInfoAnd p))
wU
wX))
-> (:>)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p) :> FL (PatchInfoAnd p))
wU
wX
-> IO
((:>)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p) :> FL (PatchInfoAnd p))
wU
wX)
forall a b. (a -> b) -> a -> b
$ (forall wU wV. PatchInfoAnd p wU wV -> Bool)
-> FL (PatchInfoAnd p) wU wX
-> (:>)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p) :> FL (PatchInfoAnd p))
wU
wX
forall (p :: * -> * -> *) wX wY.
Commute p =>
(forall wU wV. p wU wV -> Bool)
-> FL p wX wY -> (:>) (FL p) (FL p :> FL p) wX wY
partitionFL (Bool -> Bool
not (Bool -> Bool)
-> (PatchInfoAnd p wU wV -> Bool) -> PatchInfoAnd p wU wV -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PatchInfo -> [PatchInfo] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [PatchInfo]
avoided) (PatchInfo -> Bool)
-> (PatchInfoAnd p wU wV -> PatchInfo)
-> PatchInfoAnd p wU wV
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatchInfoAnd p wU wV -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info) FL (PatchInfoAnd p) wU wX
them'
[DarcsFlag] -> Doc -> IO ()
putVerbose [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$
case FL (PatchInfoAnd p) wU wR
us' of
(x :: FL (PatchInfoAnd p) wU wR
x@(PatchInfoAnd p wU wY
_ :>: FL (PatchInfoAnd p) wY wR
_)) ->
String -> Doc
text String
"We have the following new (to them) patches:" Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat ((forall wW wZ. PatchInfoAnd p wW wZ -> Doc)
-> FL (PatchInfoAnd p) wU wR -> [Doc]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL PatchInfoAnd p wW wZ -> Doc
forall wW wZ. PatchInfoAnd p wW wZ -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description FL (PatchInfoAnd p) wU wR
x)
FL (PatchInfoAnd p) wU wR
_ -> Doc
forall a. Monoid a => a
mempty
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FL (PatchInfoAnd p) wU wZ -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PatchInfoAnd p) wU wZ
ps) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [DarcsFlag] -> Doc -> IO ()
putVerbose [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> Doc
text String
"They have the following patches to pull:" Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat ((forall wW wZ. PatchInfoAnd p wW wZ -> Doc)
-> FL (PatchInfoAnd p) wU wZ -> [Doc]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL PatchInfoAnd p wW wZ -> Doc
forall wW wZ. PatchInfoAnd p wW wZ -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description FL (PatchInfoAnd p) wU wZ
ps)
(Bool
hadConflicts, Sealed FL (PatchInfoAnd p) wU wX
psFiltered)
<- if PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe AllowConflicts)
PrimDarcsOption (Maybe AllowConflicts)
O.conflictsYes PrimDarcsOption (Maybe AllowConflicts)
-> [DarcsFlag] -> Maybe AllowConflicts
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts Maybe AllowConflicts -> Maybe AllowConflicts -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe AllowConflicts
forall a. Maybe a
Nothing
then Repository 'RW p wU wR
-> UseIndex
-> FL (PatchInfoAnd p) wU wR
-> FL (PatchInfoAnd p) wU wZ
-> IO (Bool, Sealed (FL (PatchInfoAnd p) wU))
forall (p :: * -> * -> *) (rt :: AccessType) wU wR wX wZ.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wU wR
-> UseIndex
-> FL (PatchInfoAnd p) wX wR
-> FL (PatchInfoAnd p) wX wZ
-> IO (Bool, Sealed (FL (PatchInfoAnd p) wX))
filterOutConflicts Repository 'RW p wU wR
repository (PrimOptSpec DarcsOptDescr DarcsFlag a UseIndex
PrimDarcsOption UseIndex
O.useIndex PrimDarcsOption UseIndex -> [DarcsFlag] -> UseIndex
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) FL (PatchInfoAnd p) wU wR
us' FL (PatchInfoAnd p) wU wZ
ps
else (Bool, Sealed (FL (PatchInfoAnd p) wU))
-> IO (Bool, Sealed (FL (PatchInfoAnd p) wU))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, FL (PatchInfoAnd p) wU wZ -> Sealed (FL (PatchInfoAnd p) wU)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed FL (PatchInfoAnd p) wU wZ
ps)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
hadConflicts (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"Skipping some patches which would cause conflicts."
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (FL (PatchInfoAnd p) wU wX -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PatchInfoAnd p) wU wX
psFiltered) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
"No remote patches to pull in!"
FL (PatchInfoAnd p) wU wX -> IO ()
forall (p :: * -> * -> *) wX wY.
RepoPatch p =>
FL (PatchInfoAnd p) wX wY -> IO ()
setEnvDarcsPatches FL (PatchInfoAnd p) wU wX
psFiltered
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (PrimOptSpec DarcsOptDescr DarcsFlag a Reorder
PrimDarcsOption Reorder
reorder PrimDarcsOption Reorder -> [DarcsFlag] -> Reorder
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts Reorder -> Reorder -> Bool
forall a. Eq a => a -> a -> Bool
/= Reorder
O.Reorder) IO ()
forall a. IO a
exitSuccess
let direction :: WhichChanges
direction = if PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
changesReverse PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts then WhichChanges
FirstReversed else WhichChanges
First
selection_config :: SelectionConfig (PatchInfoAnd p)
selection_config = WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter (PatchInfoAnd p))
-> Maybe [AnchoredPath]
-> SelectionConfig (PatchInfoAnd p)
forall (p :: * -> * -> *).
Matchable p =>
WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter p)
-> Maybe [AnchoredPath]
-> SelectionConfig p
selectionConfig WhichChanges
direction String
jobname ([DarcsFlag] -> PatchSelectionOptions
pullPatchSelOpts [DarcsFlag]
opts) Maybe (Splitter (PatchInfoAnd p))
forall a. Maybe a
Nothing Maybe [AnchoredPath]
forall a. Maybe a
Nothing
(FL (PatchInfoAnd p) wU wZ
to_be_pulled :> FL (PatchInfoAnd p) wZ wX
_) <- FL (PatchInfoAnd p) wU wX
-> SelectionConfig (PatchInfoAnd p)
-> IO ((:>) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) wU wX)
forall (p :: * -> * -> *) wX wY.
(MatchableRP p, ShowPatch p, ShowContextPatch p,
ApplyState p ~ Tree, ApplyState p ~ ApplyState (PrimOf p)) =>
FL p wX wY -> SelectionConfig p -> IO ((:>) (FL p) (FL p) wX wY)
runSelection FL (PatchInfoAnd p) wU wX
psFiltered SelectionConfig (PatchInfoAnd p)
selection_config
Sealed
(Fork
(PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR)
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wZ
-> Sealed
(Fork
(PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed (PatchSet p Origin wU
-> FL (PatchInfoAnd p) wU wR
-> FL (PatchInfoAnd p) wU wZ
-> Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR
wZ
forall (common :: * -> * -> *) (left :: * -> * -> *)
(right :: * -> * -> *) wA wX wY wU.
common wA wU
-> left wU wX -> right wU wY -> Fork common left right wA wX wY
Fork PatchSet p Origin wU
common FL (PatchInfoAnd p) wU wR
us' FL (PatchInfoAnd p) wU wZ
to_be_pulled))
fetchPatches AbsolutePath
_ [DarcsFlag]
_ [] String
jobname Repository 'RW p wU wR
_ = String
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR)))
-> String
-> IO
(Sealed
(Fork
(PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p))
Origin
wR))
forall a b. (a -> b) -> a -> b
$
String
"No default repository to " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
jobname String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" from, please specify one"
makeBundle :: forall p wR . (RepoPatch p, ApplyState p ~ Tree)
=> [DarcsFlag]
-> (Sealed (Fork (PatchSet p)
(FL (PatchInfoAnd p))
(FL (PatchInfoAnd p)) Origin wR))
-> IO ()
makeBundle :: forall (p :: * -> * -> *) wR.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> Sealed
(Fork
(PatchSet p) (FL (PatchInfoAnd p)) (FL (PatchInfoAnd p)) Origin wR)
-> IO ()
makeBundle [DarcsFlag]
opts (Sealed (Fork PatchSet p Origin wU
common FL (PatchInfoAnd p) wU wR
_ FL (PatchInfoAnd p) wU wX
to_be_fetched)) =
do
Doc
bundle <- Maybe (ApplyState p IO)
-> PatchSet p Origin wU -> FL (Named p) wU wX -> IO Doc
forall (p :: * -> * -> *) wStart wX wY.
(RepoPatch p, ApplyMonadTrans (ApplyState p) IO,
ObjectId (ObjectIdOfPatch p)) =>
Maybe (ApplyState p IO)
-> PatchSet p wStart wX -> FL (Named p) wX wY -> IO Doc
Bundle.makeBundle Maybe (Tree IO)
Maybe (ApplyState p IO)
forall a. Maybe a
Nothing PatchSet p Origin wU
common (FL (Named p) wU wX -> IO Doc) -> FL (Named p) wU wX -> IO Doc
forall a b. (a -> b) -> a -> b
$
(forall wW wY. PatchInfoAnd p wW wY -> Named p wW wY)
-> FL (PatchInfoAnd p) wU wX -> FL (Named p) wU wX
forall (a :: * -> * -> *) (b :: * -> * -> *) wX wZ.
(forall wW wY. a wW wY -> b wW wY) -> FL a wX wZ -> FL b wX wZ
mapFL_FL PatchInfoAndG (Named p) wW wY -> Named p wW wY
forall wW wY. PatchInfoAnd p wW wY -> Named p wW wY
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> p wA wB
hopefully FL (PatchInfoAnd p) wU wX
to_be_fetched
let fname :: IO String
fname = case FL (PatchInfoAnd p) wU wX
to_be_fetched of
(PatchInfoAnd p wU wY
x:>:FL (PatchInfoAnd p) wY wX
_)-> String -> IO String
getUniqueDPatchName (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ PatchInfoAnd p wU wY -> String
forall (p :: * -> * -> *) wX wY. PatchInfoAnd p wX wY -> String
patchDesc PatchInfoAnd p wU wY
x
FL (PatchInfoAnd p) wU wX
_ -> String -> IO String
forall a. Partial => String -> a
error String
"impossible case"
AbsolutePathOrStd
o <- IO AbsolutePathOrStd
-> Maybe (IO AbsolutePathOrStd) -> IO AbsolutePathOrStd
forall a. a -> Maybe a -> a
fromMaybe (AbsolutePathOrStd -> IO AbsolutePathOrStd
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AbsolutePathOrStd
stdOut) ([DarcsFlag] -> IO String -> Maybe (IO AbsolutePathOrStd)
getOutput [DarcsFlag]
opts IO String
fname)
(AbsolutePath -> Doc -> IO ())
-> (Doc -> IO ()) -> AbsolutePathOrStd -> Doc -> IO ()
forall a. (AbsolutePath -> a) -> a -> AbsolutePathOrStd -> a
useAbsoluteOrStd AbsolutePath -> Doc -> IO ()
forall p. FilePathLike p => p -> Doc -> IO ()
writeDocBinFile Doc -> IO ()
putDoc AbsolutePathOrStd
o Doc
bundle
readRepos :: RepoPatch p
=> Repository rt p wU wR -> [DarcsFlag] -> [String]
-> IO (SealedPatchSet p Origin,SealedPatchSet p Origin)
readRepos :: forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR
-> [DarcsFlag]
-> [String]
-> IO (SealedPatchSet p Origin, SealedPatchSet p Origin)
readRepos Repository rt p wU wR
_ [DarcsFlag]
_ [] = String -> IO (SealedPatchSet p Origin, SealedPatchSet p Origin)
forall a. Partial => String -> a
error String
"impossible case"
readRepos Repository rt p wU wR
to_repo [DarcsFlag]
opts [String]
us =
do [SealedPatchSet p Origin]
rs <- (String -> IO (SealedPatchSet p Origin))
-> [String] -> IO [SealedPatchSet p Origin]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\String
u -> do Repository 'RO p Any Any
r <- ReadingOrWriting
-> Repository rt p wU wR
-> UseCache
-> String
-> IO (Repository 'RO p Any Any)
forall (rt :: AccessType) (p :: * -> * -> *) wU wR vR vU.
ReadingOrWriting
-> Repository rt p wU wR
-> UseCache
-> String
-> IO (Repository 'RO p vR vU)
identifyRepositoryFor ReadingOrWriting
Reading Repository rt p wU wR
to_repo (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) String
u
PatchSet p Origin Any
ps <- Repository 'RO p Any Any -> IO (PatchSet p Origin Any)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p Any Any
r
SealedPatchSet p Origin -> IO (SealedPatchSet p Origin)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SealedPatchSet p Origin -> IO (SealedPatchSet p Origin))
-> SealedPatchSet p Origin -> IO (SealedPatchSet p Origin)
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin Any -> SealedPatchSet p Origin
forall (a :: * -> *) wX. a wX -> Sealed a
seal PatchSet p Origin Any
ps) [String]
us
(SealedPatchSet p Origin, SealedPatchSet p Origin)
-> IO (SealedPatchSet p Origin, SealedPatchSet p Origin)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((SealedPatchSet p Origin, SealedPatchSet p Origin)
-> IO (SealedPatchSet p Origin, SealedPatchSet p Origin))
-> (SealedPatchSet p Origin, SealedPatchSet p Origin)
-> IO (SealedPatchSet p Origin, SealedPatchSet p Origin)
forall a b. (a -> b) -> a -> b
$ case PrimDarcsOption RepoCombinator -> [DarcsFlag] -> RepoCombinator
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimOptSpec DarcsOptDescr DarcsFlag a RepoCombinator
PrimDarcsOption RepoCombinator
O.repoCombinator [DarcsFlag]
opts of
RepoCombinator
O.Intersection -> ([SealedPatchSet p Origin] -> SealedPatchSet p Origin
forall (p :: * -> * -> *).
Commute p =>
[SealedPatchSet p Origin] -> SealedPatchSet p Origin
patchSetIntersection [SealedPatchSet p Origin]
rs, PatchSet p Origin Origin -> SealedPatchSet p Origin
forall (a :: * -> *) wX. a wX -> Sealed a
seal PatchSet p Origin Origin
forall (p :: * -> * -> *). PatchSet p Origin Origin
emptyPatchSet)
RepoCombinator
O.Complement -> ([SealedPatchSet p Origin] -> SealedPatchSet p Origin
forall a. Partial => [a] -> a
headErr [SealedPatchSet p Origin]
rs, [SealedPatchSet p Origin] -> SealedPatchSet p Origin
forall (p :: * -> * -> *).
(Commute p, Merge p) =>
[SealedPatchSet p Origin] -> SealedPatchSet p Origin
patchSetUnion ([SealedPatchSet p Origin] -> SealedPatchSet p Origin)
-> [SealedPatchSet p Origin] -> SealedPatchSet p Origin
forall a b. (a -> b) -> a -> b
$ [SealedPatchSet p Origin] -> [SealedPatchSet p Origin]
forall a. Partial => [a] -> [a]
tailErr [SealedPatchSet p Origin]
rs)
RepoCombinator
O.Union -> ([SealedPatchSet p Origin] -> SealedPatchSet p Origin
forall (p :: * -> * -> *).
(Commute p, Merge p) =>
[SealedPatchSet p Origin] -> SealedPatchSet p Origin
patchSetUnion [SealedPatchSet p Origin]
rs, PatchSet p Origin Origin -> SealedPatchSet p Origin
forall (a :: * -> *) wX. a wX -> Sealed a
seal PatchSet p Origin Origin
forall (p :: * -> * -> *). PatchSet p Origin Origin
emptyPatchSet)
pullPatchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
pullPatchSelOpts :: [DarcsFlag] -> PatchSelectionOptions
pullPatchSelOpts [DarcsFlag]
flags = S.PatchSelectionOptions
{ verbosity :: Verbosity
S.verbosity = PrimOptSpec DarcsOptDescr DarcsFlag a Verbosity
PrimDarcsOption Verbosity
verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags
, matchFlags :: [MatchFlag]
S.matchFlags = MatchOption -> [DarcsFlag] -> [MatchFlag]
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimOptSpec DarcsOptDescr DarcsFlag a [MatchFlag]
MatchOption
O.matchSeveral [DarcsFlag]
flags
, interactive :: Bool
S.interactive = Bool -> [DarcsFlag] -> Bool
isInteractive Bool
True [DarcsFlag]
flags
, selectDeps :: SelectDeps
S.selectDeps = PrimOptSpec DarcsOptDescr DarcsFlag a SelectDeps
PrimDarcsOption SelectDeps
selectDeps PrimDarcsOption SelectDeps -> [DarcsFlag] -> SelectDeps
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags
, withSummary :: WithSummary
S.withSummary = PrimOptSpec DarcsOptDescr DarcsFlag a WithSummary
PrimDarcsOption WithSummary
O.withSummary PrimDarcsOption WithSummary -> [DarcsFlag] -> WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags
}