--  Copyright (C) 2002-2005 David Roundy
--
--  This program is free software; you can redistribute it and/or modify
--  it under the terms of the GNU General Public License as published by
--  the Free Software Foundation; either version 2, or (at your option)
--  any later version.
--
--  This program is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--  GNU General Public License for more details.
--
--  You should have received a copy of the GNU General Public License
--  along with this program; see the file COPYING.  If not, write to
--  the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
--  Boston, MA 02110-1301, USA.

{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.Commands.Pull ( -- * Commands.
                                pull, fetch,
                                pullCmd, StandardPatchApplier,
                                -- * Utility functions.
                                fetchPatches
                              ) where

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.Commands.Clone ( otherHelpInheritDefault )
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, defaultFlags, parseFlags, (?) )
import qualified Darcs.UI.Options.All as O
import Darcs.Repository.Flags ( UpdatePending (..) )
import Darcs.Repository
    ( Repository
    , identifyRepositoryFor
    , ReadingOrWriting(..)
    , withRepoLock
    , RepoJob(..)
    , readRepo
    , modifyCache
    , mkCache
    , cacheEntries
    , CacheLoc(..)
    , WritableOrNot(..)
    , CacheType(..)
    , filterOutConflicts
    )

import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, info, hopefully, patchDesc )
import Darcs.Patch ( IsRepoType, 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 ( addToPreflist, addRepoSource, getPreflist, showMotd )
import Darcs.Patch.Depends ( findUncommon, findCommonAndUncommon,
                             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 :: String
-> String
-> Doc
-> String
-> Int
-> [String]
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO ())
-> ([DarcsFlag] -> IO (Either String ()))
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO [String])
-> ([DarcsFlag] -> AbsolutePath -> [String] -> IO [String])
-> [DarcsOptDescr DarcsFlag]
-> [DarcsOptDescr DarcsFlag]
-> [DarcsFlag]
-> ([DarcsFlag] -> [String])
-> DarcsCommand
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 = String
-> (AbsolutePath, AbsolutePath)
-> [DarcsFlag]
-> [String]
-> IO [String]
prefArgs String
"repos"
    , commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
defaultRepo
    , commandAdvancedOptions :: [DarcsOptDescr DarcsFlag]
commandAdvancedOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  (RepoCombinator -> RemoteRepos -> NetworkOptions -> Any)
-> [DarcsOptDescr DarcsFlag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  (RepoCombinator -> RemoteRepos -> NetworkOptions -> Any)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (RepoCombinator -> RemoteRepos -> NetworkOptions -> a)
advancedOpts
    , commandBasicOptions :: [DarcsOptDescr DarcsFlag]
commandBasicOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Any)
-> [DarcsOptDescr DarcsFlag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Any)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> a)
basicOpts
    , commandDefaults :: [DarcsFlag]
commandDefaults = OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
-> [DarcsFlag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
forall a.
DarcsOption
  a
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
allOpts
    , commandCheckOptions :: [DarcsFlag] -> [String]
commandCheckOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> Any)
-> [DarcsFlag] -> [String]
forall (d :: * -> *) f a b. OptSpec d f a b -> [f] -> [String]
ocheck OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> Any)
forall a.
DarcsOption
  a
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
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 -- True
      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 -> RemoteRepos -> NetworkOptions -> a)
advancedOpts
      = PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (RemoteRepos -> NetworkOptions -> a)
  RepoCombinator
PrimDarcsOption RepoCombinator
O.repoCombinator
      PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (RemoteRepos -> NetworkOptions -> a)
  RepoCombinator
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (NetworkOptions -> a)
     (RemoteRepos -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (NetworkOptions -> a)
     (RepoCombinator -> RemoteRepos -> NetworkOptions -> 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
  (NetworkOptions -> a)
  (RemoteRepos -> NetworkOptions -> a)
PrimDarcsOption RemoteRepos
O.remoteRepos
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (NetworkOptions -> a)
  (RepoCombinator -> RemoteRepos -> NetworkOptions -> a)
-> OptSpec DarcsOptDescr DarcsFlag a (NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     a
     (RepoCombinator -> RemoteRepos -> NetworkOptions -> 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 (NetworkOptions -> a)
PrimDarcsOption NetworkOptions
O.network
    allOpts :: DarcsOption
  a
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
allOpts = OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
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
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> Maybe Bool
   -> DryRun
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Maybe Output
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
-> DarcsOption
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
     (RepoCombinator
      -> RemoteRepos
      -> NetworkOptions
      -> UseCache
      -> HooksConfig
      -> Bool
      -> Bool
      -> Bool
      -> a)
-> DarcsOption
     a
     ([MatchFlag]
      -> Maybe Bool
      -> DryRun
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Maybe Output
      -> Bool
      -> DiffAlgorithm
      -> Maybe StdCmdAction
      -> Verbosity
      -> RepoCombinator
      -> RemoteRepos
      -> NetworkOptions
      -> UseCache
      -> HooksConfig
      -> Bool
      -> Bool
      -> Bool
      -> a)
forall b c a.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a) b
-> DarcsOption a c
`withStdOpts` DarcsOption
  (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
  (RepoCombinator
   -> RemoteRepos
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (RepoCombinator -> RemoteRepos -> NetworkOptions -> a)
advancedOpts

pull :: DarcsCommand
pull :: DarcsCommand
pull = DarcsCommand :: String
-> String
-> Doc
-> String
-> Int
-> [String]
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO ())
-> ([DarcsFlag] -> IO (Either String ()))
-> ((AbsolutePath, AbsolutePath)
    -> [DarcsFlag] -> [String] -> IO [String])
-> ([DarcsFlag] -> AbsolutePath -> [String] -> IO [String])
-> [DarcsOptDescr DarcsFlag]
-> [DarcsOptDescr DarcsFlag]
-> [DarcsFlag]
-> ([DarcsFlag] -> [String])
-> DarcsCommand
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 = String
-> (AbsolutePath, AbsolutePath)
-> [DarcsFlag]
-> [String]
-> IO [String]
prefArgs String
"repos"
    , commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
defaultRepo
    , commandAdvancedOptions :: [DarcsOptDescr DarcsFlag]
commandAdvancedOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> Any)
-> [DarcsOptDescr DarcsFlag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> Any)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
advancedOpts
    , commandBasicOptions :: [DarcsOptDescr DarcsFlag]
commandBasicOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Any)
-> [DarcsOptDescr DarcsFlag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Any)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
basicOpts
    , commandDefaults :: [DarcsFlag]
commandDefaults = OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
-> [DarcsFlag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
forall a.
DarcsOption
  a
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
allOpts
    , commandCheckOptions :: [DarcsFlag] -> [String]
commandCheckOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> Any)
-> [DarcsFlag] -> [String]
forall (d :: * -> *) f a b. OptSpec d f a b -> [f] -> [String]
ocheck OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> Any)
forall a.
DarcsOption
  a
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
allOpts
    }
  where
    basicOpts :: OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
basicOpts
      = PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  [MatchFlag]
MatchOption
O.matchSeveral
      PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  [MatchFlag]
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     (Reorder
      -> Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     ([MatchFlag]
      -> Reorder
      -> Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  (Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
PrimDarcsOption Reorder
O.reorder
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     (Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     ([MatchFlag]
      -> Reorder
      -> Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  (Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
PrimDarcsOption (Maybe Bool)
O.interactive
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     (Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     ([MatchFlag]
      -> Reorder
      -> Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> 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
  (ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  (Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
PrimDarcsOption (Maybe AllowConflicts)
O.conflictsYes
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     (ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> a)
     ([MatchFlag]
      -> Reorder
      -> Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> 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
  (RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  (ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
PrimDarcsOption ExternalMerge
O.externalMerge
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> 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)
     (RunTest
      -> 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
      -> ExternalMerge
      -> RunTest
      -> 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)
  (RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
PrimDarcsOption RunTest
O.runTest
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> ExternalMerge
   -> RunTest
   -> 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
      -> ExternalMerge
      -> RunTest
      -> 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
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
advancedOpts
      = PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
  RepoCombinator
PrimDarcsOption RepoCombinator
O.repoCombinator
      PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
  RepoCombinator
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> a)
     (Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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
  (UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
  (Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
PrimDarcsOption Compression
O.compress
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> a)
     (UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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
  (RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
  (UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
PrimDarcsOption UseIndex
O.useIndex
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (SetScriptsExecutable
      -> UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
     (RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (SetScriptsExecutable
      -> UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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
  (SetScriptsExecutable
   -> UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
  (RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
PrimDarcsOption RemoteRepos
O.remoteRepos
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (SetScriptsExecutable
   -> UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
     (SetScriptsExecutable
      -> UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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 -> NetworkOptions -> a)
  (SetScriptsExecutable
   -> UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
PrimDarcsOption SetScriptsExecutable
O.setScriptsExecutable
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool -> WantGuiPause -> NetworkOptions -> a)
     (UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool -> WantGuiPause -> NetworkOptions -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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 -> NetworkOptions -> a)
  (UMask -> Bool -> WantGuiPause -> NetworkOptions -> a)
PrimDarcsOption UMask
O.umask
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool -> WantGuiPause -> NetworkOptions -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (WantGuiPause -> NetworkOptions -> a)
     (Bool -> WantGuiPause -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (WantGuiPause -> NetworkOptions -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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 -> NetworkOptions -> a)
  (Bool -> WantGuiPause -> NetworkOptions -> a)
PrimDarcsOption Bool
O.changesReverse
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (WantGuiPause -> NetworkOptions -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (NetworkOptions -> a)
     (WantGuiPause -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (NetworkOptions -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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
  (NetworkOptions -> a)
  (WantGuiPause -> NetworkOptions -> a)
PrimDarcsOption WantGuiPause
O.pauseForGui
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (NetworkOptions -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
-> OptSpec DarcsOptDescr DarcsFlag a (NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     a
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> 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 (NetworkOptions -> a)
PrimDarcsOption NetworkOptions
O.network
    allOpts :: DarcsOption
  a
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
allOpts = OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> a)
basicOpts OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> Reorder
   -> Maybe Bool
   -> Maybe AllowConflicts
   -> ExternalMerge
   -> RunTest
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> SelectDeps
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
-> DarcsOption
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
     (RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> UseCache
      -> HooksConfig
      -> Bool
      -> Bool
      -> Bool
      -> a)
-> DarcsOption
     a
     ([MatchFlag]
      -> Reorder
      -> Maybe Bool
      -> Maybe AllowConflicts
      -> ExternalMerge
      -> RunTest
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> SelectDeps
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> DiffAlgorithm
      -> Maybe StdCmdAction
      -> Verbosity
      -> RepoCombinator
      -> Compression
      -> UseIndex
      -> RemoteRepos
      -> SetScriptsExecutable
      -> UMask
      -> Bool
      -> WantGuiPause
      -> NetworkOptions
      -> UseCache
      -> HooksConfig
      -> Bool
      -> Bool
      -> Bool
      -> a)
forall b c a.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a) b
-> DarcsOption a c
`withStdOpts` DarcsOption
  (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (RepoCombinator
   -> Compression
   -> UseIndex
   -> RemoteRepos
   -> SetScriptsExecutable
   -> UMask
   -> Bool
   -> WantGuiPause
   -> NetworkOptions
   -> a)
advancedOpts

pullCmd
  :: PatchApplier pa
  => pa -> (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
pullCmd :: 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)
mapM (AbsolutePath -> String -> IO String
fixUrl AbsolutePath
o) [String]
repos
    DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob () -> IO ()
forall a.
DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob a -> IO a
withRepoLock (PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) UpdatePending
YesUpdatePending (PrimDarcsOption UMask
umask PrimDarcsOption UMask -> [DarcsFlag] -> UMask
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (RepoJob () -> IO ()) -> RepoJob () -> IO ()
forall a b. (a -> b) -> a -> b
$
     pa
-> (forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
    (IsRepoType rt, ApplierRepoTypeConstraint pa rt, RepoPatch p,
     ApplyState p ~ Tree) =>
    PatchProxy p -> Repository rt p wR wU wR -> IO ())
-> RepoJob ()
forall pa.
PatchApplier pa =>
pa
-> (forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
    (IsRepoType rt, ApplierRepoTypeConstraint pa rt, RepoPatch p,
     ApplyState p ~ Tree) =>
    PatchProxy p -> Repository rt p wR wU wR -> IO ())
-> RepoJob ()
repoJob pa
patchApplier ((forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
  (IsRepoType rt, ApplierRepoTypeConstraint pa rt, RepoPatch p,
   ApplyState p ~ Tree) =>
  PatchProxy p -> Repository rt p wR wU wR -> IO ())
 -> RepoJob ())
-> (forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
    (IsRepoType rt, ApplierRepoTypeConstraint pa rt, RepoPatch p,
     ApplyState p ~ Tree) =>
    PatchProxy p -> Repository rt p wR wU wR -> IO ())
-> RepoJob ()
forall a b. (a -> b) -> a -> b
$ \PatchProxy p
patchProxy Repository rt p wR wU wR
initRepo -> do
      let repository :: Repository rt p wR wU wR
repository = (Cache -> Cache)
-> Repository rt p wR wU wR -> Repository rt p wR wU wR
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
(Cache -> Cache)
-> Repository rt p wR wU wT -> Repository rt p wR wU wT
modifyCache ([String] -> Cache -> Cache
addReposToCache [String]
pullingFrom) Repository rt p wR wU wR
initRepo
      Sealed Fork
  (PatchSet rt p)
  (FL (PatchInfoAnd rt p))
  (FL (PatchInfoAnd rt p))
  Origin
  wR
  wX
fork <- AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository rt p wR wU wR
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt p))
           Origin
           wR))
forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository rt p wR wU wR
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt p))
           Origin
           wR))
fetchPatches AbsolutePath
o [DarcsFlag]
opts [String]
repos String
"pull" Repository rt p wR wU wR
repository
      pa
-> PatchProxy p
-> String
-> [DarcsFlag]
-> Repository rt p wR wU wR
-> Fork
     (PatchSet rt p)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p))
     Origin
     wR
     wX
-> IO ()
forall pa (rt :: RepoType) (p :: * -> * -> *) wR wU wZ.
(PatchApplier pa, ApplierRepoTypeConstraint pa rt, IsRepoType rt,
 RepoPatch p, ApplyState p ~ Tree) =>
pa
-> PatchProxy p
-> String
-> [DarcsFlag]
-> Repository rt p wR wU wR
-> Fork
     (PatchSet rt p)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p))
     Origin
     wR
     wZ
-> IO ()
applyPatches pa
patchApplier PatchProxy p
patchProxy String
"pull" [DarcsFlag]
opts Repository rt p wR wU wR
repository Fork
  (PatchSet rt p)
  (FL (PatchInfoAnd rt p))
  (FL (PatchInfoAnd rt 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 =
    DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob () -> IO ()
forall a.
DryRun -> UseCache -> UpdatePending -> UMask -> RepoJob a -> IO a
withRepoLock (PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) UpdatePending
YesUpdatePending (PrimDarcsOption UMask
umask PrimDarcsOption UMask -> [DarcsFlag] -> UMask
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (RepoJob () -> IO ()) -> RepoJob () -> IO ()
forall a b. (a -> b) -> a -> b
$ (forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
 (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
 Repository rt p wR wU wR -> IO ())
-> RepoJob ()
forall a.
(forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
 (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
 Repository rt p wR wU wR -> IO a)
-> RepoJob a
RepoJob ((forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
  (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
  Repository rt p wR wU wR -> IO ())
 -> RepoJob ())
-> (forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
    (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
    Repository rt p wR wU wR -> IO ())
-> RepoJob ()
forall a b. (a -> b) -> a -> b
$
        AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository rt p wR wU wR
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt p))
           Origin
           wR))
forall (rt :: RepoType) (p :: * -> * -> *) wR wU.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository rt p wR wU wR
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt p))
           Origin
           wR))
fetchPatches AbsolutePath
o [DarcsFlag]
opts [String]
repos String
"fetch" (Repository rt p wR wU wR
 -> IO
      (Sealed
         (Fork
            (PatchSet rt p)
            (FL (PatchInfoAnd rt p))
            (FL (PatchInfoAnd rt p))
            Origin
            wR)))
-> (Sealed
      (Fork
         (PatchSet rt p)
         (FL (PatchInfoAnd rt p))
         (FL (PatchInfoAnd rt p))
         Origin
         wR)
    -> IO ())
-> Repository rt p wR wU wR
-> IO ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> [DarcsFlag]
-> Sealed
     (Fork
        (PatchSet rt p)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p))
        Origin
        wR)
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wR.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> Sealed
     (Fork
        (PatchSet rt p)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p))
        Origin
        wR)
-> IO ()
makeBundle [DarcsFlag]
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 (Sealed (Fork (PatchSet rt p)
                                 (FL (PatchInfoAnd rt p))
                                 (FL (PatchInfoAnd rt p)) Origin wR))
fetchPatches :: AbsolutePath
-> [DarcsFlag]
-> [String]
-> String
-> Repository rt p wR wU wR
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt p))
           Origin
           wR))
fetchPatches AbsolutePath
o [DarcsFlag]
opts unfixedrepodirs :: [String]
unfixedrepodirs@(String
_:[String]
_) String
jobname Repository rt p wR wU wR
repository = do
  String
here <- IO String
getCurrentDirectory
  [String]
repodirs <- ([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 (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)
mapM (AbsolutePath -> String -> IO String
fixUrl AbsolutePath
o) [String]
unfixedrepodirs
  -- Test to make sure we aren't trying to pull from the current repo
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
repodirs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Can't pull from current repository!"
  [String]
old_default <- String -> IO [String]
getPreflist String
"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]
repodirs 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 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]
repodirs) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"..."
  (Sealed PatchSet rt p Origin wX
them, Sealed PatchSet rt p Origin wX
compl) <- Repository rt p wR wU wR
-> [DarcsFlag]
-> [String]
-> IO (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
(IsRepoType rt, RepoPatch p) =>
Repository rt p wR wU wT
-> [DarcsFlag]
-> [String]
-> IO (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
readRepos Repository rt p wR wU wR
repository [DarcsFlag]
opts [String]
repodirs
  String
-> DryRun
-> RemoteRepos
-> SetDefault
-> InheritDefault
-> Bool
-> IO ()
addRepoSource ([String] -> String
forall a. [a] -> a
head [String]
repodirs) (PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (PrimDarcsOption RemoteRepos
remoteRepos PrimDarcsOption RemoteRepos -> [DarcsFlag] -> RemoteRepos
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
      (Bool -> [DarcsFlag] -> SetDefault
setDefault Bool
False [DarcsFlag]
opts) (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_ (String -> String -> IO ()
addToPreflist String
"repos") [String]
repodirs
  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]
repodirs
  PatchSet rt p Origin wR
us <- Repository rt p wR wU wR -> IO (PatchSet rt p Origin wR)
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
(IsRepoType rt, RepoPatch p) =>
Repository rt p wR wU wT -> IO (PatchSet rt p Origin wR)
readRepo Repository rt p wR wU wR
repository
  Bool -> PatchSet rt p Origin wR -> PatchSet rt p Origin wX -> IO ()
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
RepoPatch p =>
Bool -> PatchSet rt p Origin wX -> PatchSet rt p Origin wY -> IO ()
checkUnrelatedRepos (PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimDarcsOption Bool
O.allowUnrelatedRepos [DarcsFlag]
opts) PatchSet rt p Origin wR
us PatchSet rt p Origin wX
them

  Fork PatchSet rt p Origin wU
common FL (PatchInfoAnd rt p) wU wR
us' FL (PatchInfoAnd rt p) wU wX
them' <- Fork
  (PatchSet rt p)
  (FL (PatchInfoAnd rt p))
  (FL (PatchInfoAnd rt p))
  Origin
  wR
  wX
-> IO
     (Fork
        (PatchSet rt p)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p))
        Origin
        wR
        wX)
forall (m :: * -> *) a. Monad m => a -> m a
return (Fork
   (PatchSet rt p)
   (FL (PatchInfoAnd rt p))
   (FL (PatchInfoAnd rt p))
   Origin
   wR
   wX
 -> IO
      (Fork
         (PatchSet rt p)
         (FL (PatchInfoAnd rt p))
         (FL (PatchInfoAnd rt p))
         Origin
         wR
         wX))
-> Fork
     (PatchSet rt p)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p))
     Origin
     wR
     wX
-> IO
     (Fork
        (PatchSet rt p)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p))
        Origin
        wR
        wX)
forall a b. (a -> b) -> a -> b
$ PatchSet rt p Origin wR
-> PatchSet rt p Origin wX
-> Fork
     (PatchSet rt p)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p))
     Origin
     wR
     wX
forall (rt :: RepoType) (p :: * -> * -> *) wX wY.
Commute p =>
PatchSet rt p Origin wX
-> PatchSet rt p Origin wY
-> Fork
     (PatchSet rt p)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p))
     Origin
     wX
     wY
findCommonAndUncommon PatchSet rt p Origin wR
us PatchSet rt p Origin wX
them
  FL (PatchInfoAnd rt p) wZ wR
_   :\/: FL (PatchInfoAnd rt p) wZ wX
compl' <- (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wX
-> IO
     ((:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wX)
forall (m :: * -> *) a. Monad m => a -> m a
return ((:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wX
 -> IO
      ((:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wX))
-> (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wX
-> IO
     ((:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wX)
forall a b. (a -> b) -> a -> b
$ PatchSet rt p Origin wR
-> PatchSet rt p Origin wX
-> (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wX
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
Commute p =>
PatchSet rt p Origin wX
-> PatchSet rt p Origin wY
-> (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wX wY
findUncommon PatchSet rt p Origin wR
us PatchSet rt p Origin wX
compl

  let avoided :: [PatchInfo]
avoided = (forall wW wZ. PatchInfoAnd rt p wW wZ -> PatchInfo)
-> FL (PatchInfoAnd rt p) wZ wX -> [PatchInfo]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL forall wW wZ. PatchInfoAnd rt p wW wZ -> PatchInfo
forall (rt :: RepoType) (p :: * -> * -> *) wA wB.
PatchInfoAndG rt p wA wB -> PatchInfo
info FL (PatchInfoAnd rt p) wZ wX
compl'
  FL (PatchInfoAnd rt p) wU wZ
ps :> (:>) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wZ wX
_ <- (:>)
  (FL (PatchInfoAnd rt p))
  (FL (PatchInfoAnd rt p) :> FL (PatchInfoAnd rt p))
  wU
  wX
-> IO
     ((:>)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p) :> FL (PatchInfoAnd rt p))
        wU
        wX)
forall (m :: * -> *) a. Monad m => a -> m a
return ((:>)
   (FL (PatchInfoAnd rt p))
   (FL (PatchInfoAnd rt p) :> FL (PatchInfoAnd rt p))
   wU
   wX
 -> IO
      ((:>)
         (FL (PatchInfoAnd rt p))
         (FL (PatchInfoAnd rt p) :> FL (PatchInfoAnd rt p))
         wU
         wX))
-> (:>)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p) :> FL (PatchInfoAnd rt p))
     wU
     wX
-> IO
     ((:>)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p) :> FL (PatchInfoAnd rt p))
        wU
        wX)
forall a b. (a -> b) -> a -> b
$ (forall wU wV. PatchInfoAnd rt p wU wV -> Bool)
-> FL (PatchInfoAnd rt p) wU wX
-> (:>)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p) :> FL (PatchInfoAnd rt 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)
-> (PatchInfoAndG rt (Named p) wU wV -> Bool)
-> PatchInfoAndG rt (Named p) wU wV
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PatchInfo -> [PatchInfo] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [PatchInfo]
avoided) (PatchInfo -> Bool)
-> (PatchInfoAndG rt (Named p) wU wV -> PatchInfo)
-> PatchInfoAndG rt (Named p) wU wV
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatchInfoAndG rt (Named p) wU wV -> PatchInfo
forall (rt :: RepoType) (p :: * -> * -> *) wA wB.
PatchInfoAndG rt p wA wB -> PatchInfo
info) FL (PatchInfoAnd rt p) wU wX
them'
  [DarcsFlag] -> Doc -> IO ()
putVerbose [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$
    case FL (PatchInfoAnd rt p) wU wR
us' of
      (x :: FL (PatchInfoAnd rt p) wU wR
x@(PatchInfoAnd rt p wU wY
_ :>: FL (PatchInfoAnd rt 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 rt p wW wZ -> Doc)
-> FL (PatchInfoAnd rt p) wU wR -> [Doc]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL forall wW wZ. PatchInfoAnd rt p wW wZ -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description FL (PatchInfoAnd rt p) wU wR
x)
      FL (PatchInfoAnd rt p) wU wR
_ -> Doc
forall a. Monoid a => a
mempty
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FL (PatchInfoAnd rt p) wU wZ -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PatchInfoAnd rt 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 rt p wW wZ -> Doc)
-> FL (PatchInfoAnd rt p) wU wZ -> [Doc]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL forall wW wZ. PatchInfoAnd rt p wW wZ -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description FL (PatchInfoAnd rt p) wU wZ
ps)
  (Bool
hadConflicts, Sealed FL (PatchInfoAnd rt p) wU wX
psFiltered)
    <- if 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 rt p wR wU wR
-> FL (PatchInfoAnd rt p) wU wR
-> FL (PatchInfoAnd rt p) wU wZ
-> IO (Bool, Sealed (FL (PatchInfoAnd rt p) wU))
forall (p :: * -> * -> *) (rt :: RepoType) wR wU wX wZ.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wR
-> FL (PatchInfoAnd rt p) wX wR
-> FL (PatchInfoAnd rt p) wX wZ
-> IO (Bool, Sealed (FL (PatchInfoAnd rt p) wX))
filterOutConflicts Repository rt p wR wU wR
repository FL (PatchInfoAnd rt p) wU wR
us' FL (PatchInfoAnd rt p) wU wZ
ps
        else (Bool, Sealed (FL (PatchInfoAnd rt p) wU))
-> IO (Bool, Sealed (FL (PatchInfoAnd rt p) wU))
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, FL (PatchInfoAnd rt p) wU wZ -> Sealed (FL (PatchInfoAnd rt p) wU)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed FL (PatchInfoAnd rt 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 rt p) wU wX -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PatchInfoAnd rt 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 rt p) wU wX -> IO ()
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
RepoPatch p =>
FL (PatchInfoAnd rt p) wX wY -> IO ()
setEnvDarcsPatches FL (PatchInfoAnd rt p) wU wX
psFiltered
                                Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (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 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 rt p)
selection_config = WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter (PatchInfoAnd rt p))
-> Maybe [AnchoredPath]
-> SelectionConfig (PatchInfoAnd rt 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 rt p))
forall a. Maybe a
Nothing Maybe [AnchoredPath]
forall a. Maybe a
Nothing
  (FL (PatchInfoAnd rt p) wU wZ
to_be_pulled :> FL (PatchInfoAnd rt p) wZ wX
_) <- FL (PatchInfoAnd rt p) wU wX
-> SelectionConfig (PatchInfoAnd rt p)
-> IO
     ((:>) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt 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 rt p) wU wX
psFiltered SelectionConfig (PatchInfoAnd rt p)
selection_config
  Sealed
  (Fork
     (PatchSet rt p)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt p))
     Origin
     wR)
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt p))
           Origin
           wR))
forall (m :: * -> *) a. Monad m => a -> m a
return (Fork
  (PatchSet rt p)
  (FL (PatchInfoAnd rt p))
  (FL (PatchInfoAnd rt p))
  Origin
  wR
  wZ
-> Sealed
     (Fork
        (PatchSet rt p)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p))
        Origin
        wR)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed (PatchSet rt p Origin wU
-> FL (PatchInfoAnd rt p) wU wR
-> FL (PatchInfoAnd rt p) wU wZ
-> Fork
     (PatchSet rt p)
     (FL (PatchInfoAnd rt p))
     (FL (PatchInfoAnd rt 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 rt p Origin wU
common FL (PatchInfoAnd rt p) wU wR
us' FL (PatchInfoAnd rt p) wU wZ
to_be_pulled))

fetchPatches AbsolutePath
_ [DarcsFlag]
_ [] String
jobname Repository rt p wR wU wR
_ = String
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt p))
           Origin
           wR))
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
 -> IO
      (Sealed
         (Fork
            (PatchSet rt p)
            (FL (PatchInfoAnd rt p))
            (FL (PatchInfoAnd rt p))
            Origin
            wR)))
-> String
-> IO
     (Sealed
        (Fork
           (PatchSet rt p)
           (FL (PatchInfoAnd rt p))
           (FL (PatchInfoAnd rt 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 rt p wR . (RepoPatch p, ApplyState p ~ Tree)
           => [DarcsFlag]
           -> (Sealed (Fork (PatchSet rt p)
                      (FL (PatchInfoAnd rt p))
                      (FL (PatchInfoAnd rt p)) Origin wR))
           -> IO ()
makeBundle :: [DarcsFlag]
-> Sealed
     (Fork
        (PatchSet rt p)
        (FL (PatchInfoAnd rt p))
        (FL (PatchInfoAnd rt p))
        Origin
        wR)
-> IO ()
makeBundle [DarcsFlag]
opts (Sealed (Fork PatchSet rt p Origin wU
common FL (PatchInfoAnd rt p) wU wR
_ FL (PatchInfoAnd rt p) wU wX
to_be_fetched)) =
    do
      Doc
bundle <- Maybe (Tree IO)
-> PatchSet rt p Origin wU -> FL (Named p) wU wX -> IO Doc
forall (p :: * -> * -> *) (rt :: RepoType) wStart wX wY.
(ApplyState p ~ Tree, RepoPatch p) =>
Maybe (Tree IO)
-> PatchSet rt p wStart wX -> FL (Named p) wX wY -> IO Doc
Bundle.makeBundle Maybe (Tree IO)
forall a. Maybe a
Nothing PatchSet rt 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 rt p wW wY -> Named p wW wY)
-> FL (PatchInfoAnd rt 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 forall wW wY. PatchInfoAnd rt p wW wY -> Named p wW wY
forall (rt :: RepoType) (p :: * -> * -> *) wA wB.
PatchInfoAndG rt p wA wB -> p wA wB
hopefully FL (PatchInfoAnd rt p) wU wX
to_be_fetched
      String
fname <- case FL (PatchInfoAnd rt p) wU wX
to_be_fetched of
                    (PatchInfoAnd rt p wU wY
x:>:FL (PatchInfoAnd rt p) wY wX
_)-> String -> IO String
getUniqueDPatchName (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ PatchInfoAnd rt p wU wY -> String
forall (rt :: RepoType) (p :: * -> * -> *) wX wY.
PatchInfoAnd rt p wX wY -> String
patchDesc PatchInfoAnd rt p wU wY
x
                    FL (PatchInfoAnd rt p) wU wX
_ -> String -> IO String
forall a. HasCallStack => String -> a
error String
"impossible case"
      let o :: AbsolutePathOrStd
o = AbsolutePathOrStd -> Maybe AbsolutePathOrStd -> AbsolutePathOrStd
forall a. a -> Maybe a -> a
fromMaybe AbsolutePathOrStd
stdOut ([DarcsFlag] -> String -> Maybe AbsolutePathOrStd
getOutput [DarcsFlag]
opts 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

{- Read in the specified pull-from repositories.  Perform
Intersection, Union, or Complement read.  In patch-theory terms
(stated in set algebra, where + is union and & is intersection
and \ is complement):

    Union =         ((R1 + R2 + ... + Rn) \ Rc)
    Intersection =  ((R1 & R2 & ... & Rn) \ Rc)
    Complement =    (R1 \ Rc) \ ((R2 + R3 + ... + Rn) \ Rc)

                        where Rc = local repo
                              R1 = 1st specified pull repo
                              R2, R3, Rn = other specified pull repo

Since Rc is not provided here yet, the result of readRepos is a
tuple: the first patchset(s) to be complemented against Rc and then
the second patchset(s) to be complemented against Rc.
-}

readRepos :: (IsRepoType rt, RepoPatch p)
          => Repository rt p wR wU wT -> [DarcsFlag] -> [String]
          -> IO (SealedPatchSet rt p Origin,SealedPatchSet rt p Origin)
readRepos :: Repository rt p wR wU wT
-> [DarcsFlag]
-> [String]
-> IO (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
readRepos Repository rt p wR wU wT
_ [DarcsFlag]
_ [] = String
-> IO (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
forall a. HasCallStack => String -> a
error String
"impossible case"
readRepos Repository rt p wR wU wT
to_repo [DarcsFlag]
opts [String]
us =
    do [SealedPatchSet rt p Origin]
rs <- (String -> IO (SealedPatchSet rt p Origin))
-> [String] -> IO [SealedPatchSet rt p Origin]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\String
u -> do Repository rt p Any Any Any
r <- ReadingOrWriting
-> Repository rt p wR wU wT
-> UseCache
-> String
-> IO (Repository rt p Any Any Any)
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT vR vU vT.
ReadingOrWriting
-> Repository rt p wR wU wT
-> UseCache
-> String
-> IO (Repository rt p vR vU vT)
identifyRepositoryFor ReadingOrWriting
Reading Repository rt p wR wU wT
to_repo (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 rt p Origin Any
ps <- Repository rt p Any Any Any -> IO (PatchSet rt p Origin Any)
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
(IsRepoType rt, RepoPatch p) =>
Repository rt p wR wU wT -> IO (PatchSet rt p Origin wR)
readRepo Repository rt p Any Any Any
r
                            SealedPatchSet rt p Origin -> IO (SealedPatchSet rt p Origin)
forall (m :: * -> *) a. Monad m => a -> m a
return (SealedPatchSet rt p Origin -> IO (SealedPatchSet rt p Origin))
-> SealedPatchSet rt p Origin -> IO (SealedPatchSet rt p Origin)
forall a b. (a -> b) -> a -> b
$ PatchSet rt p Origin Any -> SealedPatchSet rt p Origin
forall (a :: * -> *) wX. a wX -> Sealed a
seal PatchSet rt p Origin Any
ps) [String]
us
       (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
-> IO (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
forall (m :: * -> *) a. Monad m => a -> m a
return ((SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
 -> IO (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin))
-> (SealedPatchSet rt p Origin, SealedPatchSet rt p Origin)
-> IO (SealedPatchSet rt p Origin, SealedPatchSet rt 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 PrimDarcsOption RepoCombinator
O.repoCombinator [DarcsFlag]
opts of
                  RepoCombinator
O.Intersection -> ([SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
forall (p :: * -> * -> *) (rt :: RepoType).
Commute p =>
[SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
patchSetIntersection [SealedPatchSet rt p Origin]
rs, PatchSet rt p Origin Origin -> SealedPatchSet rt p Origin
forall (a :: * -> *) wX. a wX -> Sealed a
seal PatchSet rt p Origin Origin
forall (rt :: RepoType) (p :: * -> * -> *).
PatchSet rt p Origin Origin
emptyPatchSet)
                  RepoCombinator
O.Complement -> ([SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
forall a. [a] -> a
head [SealedPatchSet rt p Origin]
rs, [SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
forall (p :: * -> * -> *) (rt :: RepoType).
(Commute p, Merge p, Eq2 p) =>
[SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
patchSetUnion ([SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin)
-> [SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
forall a b. (a -> b) -> a -> b
$ [SealedPatchSet rt p Origin] -> [SealedPatchSet rt p Origin]
forall a. [a] -> [a]
tail [SealedPatchSet rt p Origin]
rs)
                  RepoCombinator
O.Union -> ([SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
forall (p :: * -> * -> *) (rt :: RepoType).
(Commute p, Merge p, Eq2 p) =>
[SealedPatchSet rt p Origin] -> SealedPatchSet rt p Origin
patchSetUnion [SealedPatchSet rt p Origin]
rs, PatchSet rt p Origin Origin -> SealedPatchSet rt p Origin
forall (a :: * -> *) wX. a wX -> Sealed a
seal PatchSet rt p Origin Origin
forall (rt :: RepoType) (p :: * -> * -> *).
PatchSet rt p Origin Origin
emptyPatchSet)

pullPatchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
pullPatchSelOpts :: [DarcsFlag] -> PatchSelectionOptions
pullPatchSelOpts [DarcsFlag]
flags = PatchSelectionOptions :: Verbosity
-> [MatchFlag]
-> Bool
-> SelectDeps
-> WithSummary
-> WithContext
-> PatchSelectionOptions
S.PatchSelectionOptions
    { verbosity :: Verbosity
S.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 MatchOption
O.matchSeveral [DarcsFlag]
flags
    , interactive :: Bool
S.interactive = Bool -> [DarcsFlag] -> Bool
isInteractive Bool
True [DarcsFlag]
flags
    , selectDeps :: SelectDeps
S.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 = PrimDarcsOption WithSummary
O.withSummary PrimDarcsOption WithSummary -> [DarcsFlag] -> WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags
    , withContext :: WithContext
S.withContext = PrimDarcsOption WithContext
withContext PrimDarcsOption WithContext -> [DarcsFlag] -> WithContext
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags
    }