--  Copyright (C) 2004,2007 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.

-- |
-- Copyright   : 2004, 2007 David Roundy
-- License     : GPL
-- Maintainer  : darcs-devel@darcs.net
-- Stability   : experimental
-- Portability : portable

{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.Commands.Amend
    (
      amend
    , amendrecord
    ) where

import Darcs.Prelude

import Control.Monad ( unless )
import Data.Maybe ( isNothing, isJust )

import Darcs.UI.Commands
    ( DarcsCommand(..), withStdOpts
    , commandAlias
    , nodefaults
    , setEnvDarcsFiles
    , setEnvDarcsPatches
    , amInHashedRepository
    )
import Darcs.UI.Commands.Util
    ( announceFiles
    , historyEditHelp
    , testTentativeAndMaybeExit
    )
import Darcs.UI.Completion ( modifiedFileArgs, knownFileArgs )
import Darcs.UI.Flags ( diffingOpts, pathSetFromArgs )
import Darcs.UI.Options ( Config, (?), (^) )
import qualified Darcs.UI.Options.All as O
import Darcs.UI.PatchHeader
    ( AskAboutDeps(..)
    , HijackOptions(..)
    , patchHeaderConfig
    , runHijackT
    , updatePatchHeader
    )

import Darcs.Repository.Flags ( UpdatePending(..) )
import Darcs.Patch ( RepoPatch, description, PrimOf
                   , effect, invert, invertFL, canonizeFL
                   )
import Darcs.Patch.Apply ( ApplyState )
import Darcs.Patch.Depends ( contextPatches, patchSetUnion, findCommonWithThem )
import Darcs.Patch.Info ( isTag )
import Darcs.Patch.Named ( fmapFL_Named )
import Darcs.Patch.PatchInfoAnd ( hopefully )
import Darcs.Patch.Set ( Origin, PatchSet )
import Darcs.Patch.Split ( primSplitter )
import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, info, patchDesc )
import Darcs.Patch.Rebase.Fixup ( RebaseFixup(..) )
import Darcs.Patch.Rebase.Name ( RebaseName(..) )
import Darcs.Util.Path ( AnchoredPath )
import Darcs.Repository
    ( Repository
    , AccessType(..)
    , withRepoLock
    , RepoJob(..)
    , identifyRepositoryFor
    , ReadingOrWriting(Reading)
    , tentativelyRemovePatches
    , tentativelyAddPatch
    , withManualRebaseUpdate
    , finalizeRepositoryChanges
    , readPendingAndWorking
    , readPristine
    , readPatches
    , tentativelyRemoveFromPW
    )
import Darcs.Repository.Pending ( readTentativePending, writeTentativePending )
import Darcs.Repository.Prefs ( getDefaultRepo )
import Darcs.UI.SelectChanges
    ( WhichChanges(..)
    , selectionConfigPrim
    , runInvertibleSelection
    , withSelectedPatchFromList
    )
import qualified Darcs.UI.SelectChanges as S
    ( PatchSelectionOptions(..)
    )
import Darcs.Util.Exception ( clarifyErrors )
import Darcs.Patch.Witnesses.Ordered
    ( FL(..), RL, (:>)(..), (+>+)
    , nullFL, reverseRL, reverseFL, mapFL_FL
    )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..) )

import Darcs.Util.English ( anyOfClause, itemizeVertical )
import Darcs.Util.Printer ( Doc, formatWords, putDocLn, text, (<+>), ($$), ($+$) )
import Darcs.Util.Printer.Color ( ePutDocLn )
import Darcs.Util.Tree( Tree )


amendDescription :: String
amendDescription :: String
amendDescription = String
"Improve a patch before it leaves your repository."


amendHelp :: Doc
amendHelp :: Doc
amendHelp =
  [String] -> Doc
formatWords
  [ String
"Amend updates a \"draft\" patch with additions or improvements,"
  , String
"resulting in a single \"finished\" patch."
  ]
  Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
  [ String
"By default `amend` proposes you to record additional changes."
  , String
"If instead you want to remove changes, use the flag `--unrecord`."
  ]
  Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
  [ String
"When recording a draft patch, it is a good idea to start the name with"
  , String
"`DRAFT:`. When done, remove it with `darcs amend --edit-long-comment`."
  , String
"Alternatively, to change the patch name without starting an editor, "
  , String
"use the `--name`/`-m` flag:"
  ]
  Doc -> Doc -> Doc
$+$ String -> Doc
text
    String
"    darcs amend --match 'name \"DRAFT: foo\"' --name 'foo2'"
  Doc -> Doc -> Doc
$+$ [String] -> Doc
formatWords
  [ String
"Like `darcs record`, if you call amend with files as arguments,"
  , String
"you will only be asked about changes to those files.  So to amend a"
  , String
"patch to foo.c with improvements in bar.c, you would run:"
  ]
  Doc -> Doc -> Doc
$+$ String -> Doc
text
    String
"    darcs amend --match 'touch foo.c' bar.c"
  Doc -> Doc -> Doc
$+$ Doc
historyEditHelp

amend :: DarcsCommand
amend :: DarcsCommand
amend = DarcsCommand
    {
      commandProgramName :: String
commandProgramName          = String
"darcs"
    , commandName :: String
commandName                 = String
"amend"
    , commandHelp :: Doc
commandHelp                 = Doc
amendHelp
    , commandDescription :: String
commandDescription          = String
amendDescription
    , commandExtraArgs :: Int
commandExtraArgs            = -Int
1
    , commandExtraArgHelp :: [String]
commandExtraArgHelp         = [String
"[FILE or DIRECTORY]..."]
    , commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
commandCommand              = (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
amendCmd
    , commandPrereq :: [DarcsFlag] -> IO (Either String ())
commandPrereq               = [DarcsFlag] -> IO (Either String ())
amInHashedRepository
    , commandCompleteArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
commandCompleteArgs         = (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
fileArgs
    , commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults          = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
nodefaults
    , commandOptions :: CommandOptions
commandOptions              = CommandOptions
allOpts
    }
  where
    fileArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
fileArgs (AbsolutePath, AbsolutePath)
fps [DarcsFlag]
flags [String]
args =
      if (PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.amendUnrecord PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags)
        then (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
knownFileArgs (AbsolutePath, AbsolutePath)
fps [DarcsFlag]
flags [String]
args
        else (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
modifiedFileArgs (AbsolutePath, AbsolutePath)
fps [DarcsFlag]
flags [String]
args
    basicOpts :: OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
basicOpts
      = PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  ([NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  Bool
PrimDarcsOption Bool
O.amendUnrecord
      PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  ([NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  Bool
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     ([MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     ([NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     ([MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
  ([MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  ([NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption [NotInRemote]
O.notInRemote
      OptSpec
  DarcsOptDescr
  DarcsFlag
  ([MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     ([MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
forall (d :: * -> *) f b c a.
OptSpec d f b c -> OptSpec d f a b -> OptSpec d f a c
^ OptSpec
  DarcsOptDescr
  DarcsFlag
  (TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  ([MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
MatchOption
O.matchOneNontag
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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 String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption TestChanges
O.testChanges
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption (Maybe Bool)
O.interactive --True
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption (Maybe String)
O.author
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption Bool
O.selectAuthor
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption (Maybe String)
O.patchname
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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 AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption Bool
O.askDeps
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption (Maybe AskLongComment)
O.askLongComment
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
  (LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption Bool
O.keepDate
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (LookForReplaces
      -> LookForMoves -> Maybe String -> DiffAlgorithm -> a)
     (LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> DiffAlgorithm
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (LookForReplaces
      -> LookForMoves -> Maybe String -> DiffAlgorithm -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
  (LookForReplaces
   -> LookForMoves -> Maybe String -> DiffAlgorithm -> a)
  (LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
PrimDarcsOption LookForAdds
O.lookforadds
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (LookForReplaces
   -> LookForMoves -> Maybe String -> DiffAlgorithm -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (LookForMoves -> Maybe String -> DiffAlgorithm -> a)
     (LookForReplaces
      -> LookForMoves -> Maybe String -> DiffAlgorithm -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (LookForMoves -> Maybe String -> DiffAlgorithm -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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
  (LookForMoves -> Maybe String -> DiffAlgorithm -> a)
  (LookForReplaces
   -> LookForMoves -> Maybe String -> DiffAlgorithm -> a)
PrimDarcsOption LookForReplaces
O.lookforreplaces
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (LookForMoves -> Maybe String -> DiffAlgorithm -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String -> DiffAlgorithm -> a)
     (LookForMoves -> Maybe String -> DiffAlgorithm -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String -> DiffAlgorithm -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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 -> DiffAlgorithm -> a)
  (LookForMoves -> Maybe String -> DiffAlgorithm -> a)
PrimDarcsOption LookForMoves
O.lookformoves
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe String -> DiffAlgorithm -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (DiffAlgorithm -> a)
     (Maybe String -> DiffAlgorithm -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (DiffAlgorithm -> a)
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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)
  (Maybe String -> DiffAlgorithm -> a)
PrimDarcsOption (Maybe String)
O.repoDir
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (DiffAlgorithm -> a)
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
-> OptSpec DarcsOptDescr DarcsFlag a (DiffAlgorithm -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     a
     (Bool
      -> [NotInRemote]
      -> [MatchFlag]
      -> TestChanges
      -> Maybe Bool
      -> Maybe String
      -> Bool
      -> Maybe String
      -> Bool
      -> Maybe AskLongComment
      -> Bool
      -> LookForAdds
      -> LookForReplaces
      -> LookForMoves
      -> Maybe String
      -> 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 (UMask -> SetScriptsExecutable -> a)
advancedOpts
      = PrimOptSpec
  DarcsOptDescr DarcsFlag (SetScriptsExecutable -> a) UMask
PrimDarcsOption UMask
O.umask
      PrimOptSpec
  DarcsOptDescr DarcsFlag (SetScriptsExecutable -> a) UMask
-> OptSpec DarcsOptDescr DarcsFlag a (SetScriptsExecutable -> a)
-> OptSpec
     DarcsOptDescr DarcsFlag a (UMask -> SetScriptsExecutable -> 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 (SetScriptsExecutable -> a)
PrimDarcsOption SetScriptsExecutable
O.setScriptsExecutable
    allOpts :: CommandOptions
allOpts = DarcsOption
  (Maybe StdCmdAction
   -> Verbosity
   -> UMask
   -> SetScriptsExecutable
   -> UseCache
   -> UseIndex
   -> HooksConfig
   -> Bool
   -> Bool
   -> [DarcsFlag])
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> UMask
   -> SetScriptsExecutable
   -> UseCache
   -> UseIndex
   -> HooksConfig
   -> Bool
   -> Bool
   -> [DarcsFlag])
-> DarcsOption
     (UseCache
      -> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
     (UMask
      -> SetScriptsExecutable
      -> UseCache
      -> UseIndex
      -> HooksConfig
      -> Bool
      -> Bool
      -> [DarcsFlag])
-> CommandOptions
forall b c.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
     (UseCache
      -> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
     b
-> CommandOptions
withStdOpts DarcsOption
  (Maybe StdCmdAction
   -> Verbosity
   -> UMask
   -> SetScriptsExecutable
   -> UseCache
   -> UseIndex
   -> HooksConfig
   -> Bool
   -> Bool
   -> [DarcsFlag])
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> Maybe StdCmdAction
   -> Verbosity
   -> UMask
   -> SetScriptsExecutable
   -> UseCache
   -> UseIndex
   -> HooksConfig
   -> Bool
   -> Bool
   -> [DarcsFlag])
forall {a}.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (Bool
   -> [NotInRemote]
   -> [MatchFlag]
   -> TestChanges
   -> Maybe Bool
   -> Maybe String
   -> Bool
   -> Maybe String
   -> Bool
   -> Maybe AskLongComment
   -> Bool
   -> LookForAdds
   -> LookForReplaces
   -> LookForMoves
   -> Maybe String
   -> DiffAlgorithm
   -> a)
basicOpts DarcsOption
  (UseCache
   -> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
  (UMask
   -> SetScriptsExecutable
   -> UseCache
   -> UseIndex
   -> HooksConfig
   -> Bool
   -> Bool
   -> [DarcsFlag])
forall {a}.
OptSpec
  DarcsOptDescr DarcsFlag a (UMask -> SetScriptsExecutable -> a)
advancedOpts
    amendCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
amendCmd (AbsolutePath, AbsolutePath)
fps [DarcsFlag]
flags [String]
args = (AbsolutePath, AbsolutePath)
-> [String] -> IO (Maybe [AnchoredPath])
pathSetFromArgs (AbsolutePath, AbsolutePath)
fps [String]
args IO (Maybe [AnchoredPath])
-> (Maybe [AnchoredPath] -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [DarcsFlag] -> Maybe [AnchoredPath] -> IO ()
doAmend [DarcsFlag]
flags

amendrecord :: DarcsCommand
amendrecord :: DarcsCommand
amendrecord = String -> Maybe DarcsCommand -> DarcsCommand -> DarcsCommand
commandAlias String
"amend-record" Maybe DarcsCommand
forall a. Maybe a
Nothing DarcsCommand
amend

doAmend :: Config -> Maybe [AnchoredPath] -> IO ()
doAmend :: [DarcsFlag] -> Maybe [AnchoredPath] -> IO ()
doAmend [DarcsFlag]
cfg Maybe [AnchoredPath]
files =
  UseCache -> UMask -> RepoJob 'RW () -> IO ()
forall a. UseCache -> UMask -> RepoJob 'RW a -> IO a
withRepoLock (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
O.useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg) (PrimOptSpec DarcsOptDescr DarcsFlag a UMask
PrimDarcsOption UMask
O.umask PrimDarcsOption UMask -> [DarcsFlag] -> UMask
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg) (RepoJob 'RW () -> IO ()) -> RepoJob 'RW () -> IO ()
forall a b. (a -> b) -> a -> b
$
      TreePatchJob 'RW () -> RepoJob 'RW ()
forall (rt :: AccessType) a. TreePatchJob rt a -> RepoJob rt a
RepoJob (TreePatchJob 'RW () -> RepoJob 'RW ())
-> TreePatchJob 'RW () -> RepoJob 'RW ()
forall a b. (a -> b) -> a -> b
$ \(Repository 'RW p wU wR
repository :: Repository 'RW p wU wR) -> do
    PatchSet p Origin wR
patchSet <- Repository 'RW p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RW p wU wR
repository
    PatchSet p Origin wZ
_ :> RL (PatchInfoAnd p) wZ wR
candidates <- [DarcsFlag]
-> Repository 'RW p wU wR
-> PatchSet p Origin wR
-> IO ((:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR)
forall (p :: * -> * -> *) wU wR.
RepoPatch p =>
[DarcsFlag]
-> Repository 'RW p wU wR
-> PatchSet p Origin wR
-> IO ((:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR)
filterNotInRemote [DarcsFlag]
cfg Repository 'RW p wU wR
repository PatchSet p Origin wR
patchSet
    String
-> RL (PatchInfoAnd p) wZ wR
-> PatchSelectionOptions
-> ((:>) (RL (PatchInfoAnd p)) (PatchInfoAnd p) wZ wR -> IO ())
-> IO ()
forall (p :: * -> * -> *) wX wY.
(Commute p, Matchable p, ShowPatch p, ShowContextPatch p,
 ApplyState p ~ Tree) =>
String
-> RL p wX wY
-> PatchSelectionOptions
-> ((:>) (RL p) p wX wY -> IO ())
-> IO ()
withSelectedPatchFromList String
"amend" RL (PatchInfoAnd p) wZ wR
candidates ([DarcsFlag] -> PatchSelectionOptions
patchSelOpts [DarcsFlag]
cfg) (((:>) (RL (PatchInfoAnd p)) (PatchInfoAnd p) wZ wR -> IO ())
 -> IO ())
-> ((:>) (RL (PatchInfoAnd p)) (PatchInfoAnd p) wZ wR -> IO ())
-> IO ()
forall a b. (a -> b) -> a -> b
$
     \(RL (PatchInfoAnd p) wZ wZ
kept :> PatchInfoAnd p wZ wR
oldp) -> do
      Verbosity -> Maybe [AnchoredPath] -> String -> IO ()
announceFiles (PrimOptSpec DarcsOptDescr DarcsFlag a Verbosity
PrimDarcsOption Verbosity
O.verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg) Maybe [AnchoredPath]
files String
"Amending changes in"
      FL (PrimOf p) wR wZ
pending :> FL (PrimOf p) wZ wU
working <-
        DiffOpts
-> Repository 'RW p wU wR
-> Maybe [AnchoredPath]
-> IO ((:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
DiffOpts
-> Repository rt p wU wR
-> Maybe [AnchoredPath]
-> IO ((:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU)
readPendingAndWorking ([DarcsFlag] -> DiffOpts
diffingOpts [DarcsFlag]
cfg) Repository 'RW p wU wR
repository Maybe [AnchoredPath]
files
      -- auxiliary function needed because the witness types differ for the
      -- isTag case
      let go :: FL (PrimOf p) wR wU1 -> IO ()
          go :: forall wU1. FL (PrimOf p) wR wU1 -> IO ()
go FL (PrimOf p) wR wU1
NilFL | Bool -> Bool
not ([DarcsFlag] -> Bool
hasEditMetadata [DarcsFlag]
cfg) = [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
cfg Doc
"No changes!"
          go FL (PrimOf p) wR wU1
ch = do
            let selection_config :: SelectionConfig (PrimOf p)
selection_config =
                   WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter (PrimOf p))
-> Maybe [AnchoredPath]
-> SelectionConfig (PrimOf p)
forall (prim :: * -> * -> *).
WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter prim)
-> Maybe [AnchoredPath]
-> SelectionConfig prim
selectionConfigPrim WhichChanges
First String
"record"
                       ([DarcsFlag] -> PatchSelectionOptions
patchSelOpts [DarcsFlag]
cfg)
                       (Splitter (PrimOf p) -> Maybe (Splitter (PrimOf p))
forall a. a -> Maybe a
Just (DiffAlgorithm -> Splitter (PrimOf p)
forall (p :: * -> * -> *).
PrimPatch p =>
DiffAlgorithm -> Splitter p
primSplitter (PrimOptSpec DarcsOptDescr DarcsFlag a DiffAlgorithm
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm PrimDarcsOption DiffAlgorithm -> [DarcsFlag] -> DiffAlgorithm
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg)))
                       Maybe [AnchoredPath]
files
            (FL (PrimOf p) wR wZ
chosenPatches :> FL (PrimOf p) wZ wU1
_) <- FL (PrimOf p) wR wU1
-> SelectionConfig (PrimOf p)
-> IO ((:>) (FL (PrimOf p)) (FL (PrimOf p)) wR wU1)
forall (p :: * -> * -> *) wX wY.
(Invert p, MatchableRP p, ShowPatch p, ShowContextPatch p,
 ApplyState p ~ Tree) =>
FL p wX wY -> SelectionConfig p -> IO ((:>) (FL p) (FL p) wX wY)
runInvertibleSelection FL (PrimOf p) wR wU1
ch SelectionConfig (PrimOf p)
selection_config
            [DarcsFlag]
-> Repository 'RW p wU wR
-> RL (PatchInfoAnd p) wZ wZ
-> PatchInfoAnd p wZ wR
-> FL (PrimOf p) wR wZ
-> FL (PrimOf p) wR wZ
-> FL (PrimOf p) wZ wU
-> IO ()
forall (p :: * -> * -> *) wU wR wC wX wY wP.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> Repository 'RW p wU wR
-> RL (PatchInfoAnd p) wC wX
-> PatchInfoAnd p wX wR
-> FL (PrimOf p) wR wY
-> FL (PrimOf p) wR wP
-> FL (PrimOf p) wP wU
-> IO ()
addChangesToPatch [DarcsFlag]
cfg Repository 'RW p wU wR
repository RL (PatchInfoAnd p) wZ wZ
kept PatchInfoAnd p wZ wR
oldp FL (PrimOf p) wR wZ
chosenPatches FL (PrimOf p) wR wZ
pending FL (PrimOf p) wZ wU
working
      if Bool -> Bool
not (PatchInfo -> Bool
isTag (PatchInfoAnd p wZ wR -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAnd p wZ wR
oldp))
        -- amending a normal patch
        then
          if PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.amendUnrecord PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg
            then do
              let selection_config :: SelectionConfig (PrimOf p)
selection_config =
                    WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter (PrimOf p))
-> Maybe [AnchoredPath]
-> SelectionConfig (PrimOf p)
forall (prim :: * -> * -> *).
WhichChanges
-> String
-> PatchSelectionOptions
-> Maybe (Splitter prim)
-> Maybe [AnchoredPath]
-> SelectionConfig prim
selectionConfigPrim WhichChanges
Last String
"unrecord" ([DarcsFlag] -> PatchSelectionOptions
patchSelOpts [DarcsFlag]
cfg)
                      (Splitter (PrimOf p) -> Maybe (Splitter (PrimOf p))
forall a. a -> Maybe a
Just (DiffAlgorithm -> Splitter (PrimOf p)
forall (p :: * -> * -> *).
PrimPatch p =>
DiffAlgorithm -> Splitter p
primSplitter (PrimOptSpec DarcsOptDescr DarcsFlag a DiffAlgorithm
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm PrimDarcsOption DiffAlgorithm -> [DarcsFlag] -> DiffAlgorithm
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg)))
                      Maybe [AnchoredPath]
files
              (FL (PrimOf p) wZ wZ
_ :> FL (PrimOf p) wZ wR
chosenPrims) <-
                FL (PrimOf p) wZ wR
-> SelectionConfig (PrimOf p)
-> IO ((:>) (FL (PrimOf p)) (FL (PrimOf p)) wZ wR)
forall (p :: * -> * -> *) wX wY.
(Invert p, MatchableRP p, ShowPatch p, ShowContextPatch p,
 ApplyState p ~ Tree) =>
FL p wX wY -> SelectionConfig p -> IO ((:>) (FL p) (FL p) wX wY)
runInvertibleSelection (PatchInfoAnd p wZ wR -> FL (PrimOf (PatchInfoAnd p)) wZ wR
forall wX wY.
PatchInfoAndG (Named p) wX wY -> FL (PrimOf (PatchInfoAnd p)) wX wY
forall (p :: * -> * -> *) wX wY.
Effect p =>
p wX wY -> FL (PrimOf p) wX wY
effect PatchInfoAnd p wZ wR
oldp) SelectionConfig (PrimOf p)
selection_config
              let invPrims :: FL (PrimOf p) wR wZ
invPrims = RL (PrimOf p) wR wZ -> FL (PrimOf p) wR wZ
forall (a :: * -> * -> *) wX wZ. RL a wX wZ -> FL a wX wZ
reverseRL (FL (PrimOf p) wZ wR -> RL (PrimOf p) wR wZ
forall (p :: * -> * -> *) wX wY.
Invert p =>
FL p wX wY -> RL p wY wX
invertFL FL (PrimOf p) wZ wR
chosenPrims)
              [DarcsFlag]
-> Repository 'RW p wU wR
-> RL (PatchInfoAnd p) wZ wZ
-> PatchInfoAnd p wZ wR
-> FL (PrimOf p) wR wZ
-> FL (PrimOf p) wR wZ
-> FL (PrimOf p) wZ wU
-> IO ()
forall (p :: * -> * -> *) wU wR wC wX wY wP.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> Repository 'RW p wU wR
-> RL (PatchInfoAnd p) wC wX
-> PatchInfoAnd p wX wR
-> FL (PrimOf p) wR wY
-> FL (PrimOf p) wR wP
-> FL (PrimOf p) wP wU
-> IO ()
addChangesToPatch [DarcsFlag]
cfg Repository 'RW p wU wR
repository RL (PatchInfoAnd p) wZ wZ
kept PatchInfoAnd p wZ wR
oldp FL (PrimOf p) wR wZ
invPrims FL (PrimOf p) wR wZ
pending FL (PrimOf p) wZ wU
working
            else
              FL (PrimOf p) wR wU -> IO ()
forall wU1. FL (PrimOf p) wR wU1 -> IO ()
go (DiffAlgorithm -> FL (PrimOf p) wR wU -> FL (PrimOf p) wR wU
forall (prim :: * -> * -> *) wX wY.
(IsHunk prim, PrimCoalesce prim, PrimConstruct prim) =>
DiffAlgorithm -> FL prim wX wY -> FL prim wX wY
canonizeFL (PrimOptSpec DarcsOptDescr DarcsFlag a DiffAlgorithm
PrimDarcsOption DiffAlgorithm
O.diffAlgorithm PrimDarcsOption DiffAlgorithm -> [DarcsFlag] -> DiffAlgorithm
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg) (FL (PrimOf p) wR wZ
pending FL (PrimOf p) wR wZ -> FL (PrimOf p) wZ wU -> FL (PrimOf p) wR wU
forall (a :: * -> * -> *) wX wY wZ.
FL a wX wY -> FL a wY wZ -> FL a wX wZ
+>+ FL (PrimOf p) wZ wU
working))
        -- amending a tag
        else
          if [DarcsFlag] -> Bool
hasEditMetadata [DarcsFlag]
cfg Bool -> Bool -> Bool
&& Maybe [AnchoredPath] -> Bool
forall a. Maybe a -> Bool
isNothing Maybe [AnchoredPath]
files
            -- the user is not trying to add new changes to the tag so there is
            -- no reason to warn.
            then FL (PrimOf p) wR wR -> IO ()
forall wU1. FL (PrimOf p) wR wU1 -> IO ()
go FL (PrimOf p) wR wR
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL
            -- the user is trying to add new changes to a tag.
            else do
              if [DarcsFlag] -> Bool
hasEditMetadata [DarcsFlag]
cfg
                -- the user already knows that it is possible to edit tag metadata,
                -- note that s/he is providing editing options!
                then Doc -> IO ()
ePutDocLn Doc
"You cannot add new changes to a tag."
                -- the user may not be aware that s/he can edit tag metadata.
                else
                  Doc -> IO ()
ePutDocLn
                    Doc
"You cannot add new changes to a tag, but you are allowed to edit tag's metadata (see darcs help amend)."
              FL (PrimOf p) wR wR -> IO ()
forall wU1. FL (PrimOf p) wR wU1 -> IO ()
go FL (PrimOf p) wR wR
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL


addChangesToPatch
  :: (RepoPatch p, ApplyState p ~ Tree)
  => Config
  -> Repository 'RW p wU wR
  -> RL (PatchInfoAnd p) wC wX  -- ^ candidates for --ask-deps
  -> PatchInfoAnd p wX wR       -- ^ original patch
  -> FL (PrimOf p) wR wY        -- ^ changes to add
  -> FL (PrimOf p) wR wP        -- ^ pending
  -> FL (PrimOf p) wP wU        -- ^ working
  -> IO ()
addChangesToPatch :: forall (p :: * -> * -> *) wU wR wC wX wY wP.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> Repository 'RW p wU wR
-> RL (PatchInfoAnd p) wC wX
-> PatchInfoAnd p wX wR
-> FL (PrimOf p) wR wY
-> FL (PrimOf p) wR wP
-> FL (PrimOf p) wP wU
-> IO ()
addChangesToPatch [DarcsFlag]
cfg Repository 'RW p wU wR
_repository RL (PatchInfoAnd p) wC wX
context PatchInfoAnd p wX wR
oldp FL (PrimOf p) wR wY
chs FL (PrimOf p) wR wP
pending FL (PrimOf p) wP wU
working =
  if FL (PrimOf p) wR wY -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PrimOf p) wR wY
chs Bool -> Bool -> Bool
&& Bool -> Bool
not ([DarcsFlag] -> Bool
hasEditMetadata [DarcsFlag]
cfg)
    then [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
cfg Doc
"You don't want to record anything!"
    else do
      -- remember the old pending for the amend --unrecord case, see below
      Sealed FL (PrimOf p) wR wX
old_pending <- Repository 'RW p wU wR -> IO (Sealed (FL (PrimOf p) wR))
forall (p :: * -> * -> *) wU wR.
RepoPatch p =>
Repository 'RW p wU wR -> IO (Sealed (FL (PrimOf p) wR))
readTentativePending Repository 'RW p wU wR
_repository
      -- If a rebase is in progress, we want to manually update the rebase
      -- state, using the amendments directly as rebase fixups. This is
      -- necessary because otherwise we will first remove the original patch
      -- then add the amended patch,
      -- and this can lead to more conflicts than using the amendment as a fixup
      -- directly. For example, if a rename operation is amended in, the rename
      -- can be propagated to any edits to the file in the rebase state, whereas
      -- a delete then add would just cause a conflict.
      -- 
      -- We can also signal that any explicit dependencies of the old patch
      -- should be rewritten for the new patch using a 'NameFixup'.
      (Repository 'RW p wU wY
_repository, (Maybe String
mlogf, PatchInfoAnd p wX wY
newp)) <-
        Repository 'RW p wU wR
-> (Repository 'RW p wU wR
    -> IO
         (Repository 'RW p wU wY, FL (RebaseFixup (PrimOf p)) wY wR,
          (Maybe String, PatchInfoAnd p wX wY)))
-> IO
     (Repository 'RW p wU wY, (Maybe String, PatchInfoAnd p wX wY))
forall (p :: * -> * -> *) (rt :: AccessType) wU wR wR' x.
RepoPatch p =>
Repository rt p wU wR
-> (Repository rt p wU wR
    -> IO
         (Repository rt p wU wR', FL (RebaseFixup (PrimOf p)) wR' wR, x))
-> IO (Repository rt p wU wR', x)
withManualRebaseUpdate Repository 'RW p wU wR
_repository ((Repository 'RW p wU wR
  -> IO
       (Repository 'RW p wU wY, FL (RebaseFixup (PrimOf p)) wY wR,
        (Maybe String, PatchInfoAnd p wX wY)))
 -> IO
      (Repository 'RW p wU wY, (Maybe String, PatchInfoAnd p wX wY)))
-> (Repository 'RW p wU wR
    -> IO
         (Repository 'RW p wU wY, FL (RebaseFixup (PrimOf p)) wY wR,
          (Maybe String, PatchInfoAnd p wX wY)))
-> IO
     (Repository 'RW p wU wY, (Maybe String, PatchInfoAnd p wX wY))
forall a b. (a -> b) -> a -> b
$ \Repository 'RW p wU wR
_repository -> do
          -- Note we pass NoUpdatePending here and below when re-adding the
          -- amended patch, and instead fix pending explicitly further below.
          Repository 'RW p wU wX
_repository <-
            Repository 'RW p wU wR
-> UpdatePending
-> FL (PatchInfoAnd p) wX wR
-> IO (Repository 'RW p wU wX)
forall (p :: * -> * -> *) wU wR wX.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RW p wU wR
-> UpdatePending
-> FL (PatchInfoAnd p) wX wR
-> IO (Repository 'RW p wU wX)
tentativelyRemovePatches
              Repository 'RW p wU wR
_repository
              UpdatePending
NoUpdatePending
              (PatchInfoAnd p wX wR
oldp PatchInfoAnd p wX wR
-> FL (PatchInfoAnd p) wR wR -> FL (PatchInfoAnd p) wX wR
forall (a :: * -> * -> *) wX wY wZ.
a wX wY -> FL a wY wZ -> FL a wX wZ
:>: FL (PatchInfoAnd p) wR wR
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL)
          (Maybe String
mlogf, PatchInfoAnd p wX wY
newp) <-
            HijackOptions
-> HijackT IO (Maybe String, PatchInfoAnd p wX wY)
-> IO (Maybe String, PatchInfoAnd p wX wY)
forall (m :: * -> *) a.
Monad m =>
HijackOptions -> HijackT m a -> m a
runHijackT HijackOptions
AlwaysRequestHijackPermission (HijackT IO (Maybe String, PatchInfoAnd p wX wY)
 -> IO (Maybe String, PatchInfoAnd p wX wY))
-> HijackT IO (Maybe String, PatchInfoAnd p wX wY)
-> IO (Maybe String, PatchInfoAnd p wX wY)
forall a b. (a -> b) -> a -> b
$
            String
-> AskAboutDeps p wX
-> PatchSelectionOptions
-> PatchHeaderConfig
-> Named (PrimOf p) wX wR
-> FL (PrimOf p) wR wY
-> HijackT IO (Maybe String, PatchInfoAnd p wX wY)
forall (p :: * -> * -> *) wX wY wZ.
(RepoPatch p, ApplyState p ~ Tree) =>
String
-> AskAboutDeps p wX
-> PatchSelectionOptions
-> PatchHeaderConfig
-> Named (PrimOf p) wX wY
-> FL (PrimOf p) wY wZ
-> HijackT IO (Maybe String, PatchInfoAnd p wX wZ)
updatePatchHeader
              String
"amend"
              (if PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.askDeps PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg
                 then RL (PatchInfoAnd p) wC wX -> AskAboutDeps p wX
forall (p :: * -> * -> *) w wX.
RL (PatchInfoAnd p) w wX -> AskAboutDeps p wX
AskAboutDeps RL (PatchInfoAnd p) wC wX
context
                 else AskAboutDeps p wX
forall (p :: * -> * -> *) wX. AskAboutDeps p wX
NoAskAboutDeps)
              ([DarcsFlag] -> PatchSelectionOptions
patchSelOpts [DarcsFlag]
cfg)
              ([DarcsFlag] -> PatchHeaderConfig
patchHeaderConfig [DarcsFlag]
cfg)
              ((FL p wX wR -> FL (PrimOf p) wX wR)
-> Named p wX wR -> Named (PrimOf p) wX wR
forall (p :: * -> * -> *) wA wB (q :: * -> * -> *) wC wD.
(FL p wA wB -> FL q wC wD) -> Named p wA wB -> Named q wC wD
fmapFL_Named FL p wX wR -> FL (PrimOf p) wX wR
FL p wX wR -> FL (PrimOf (FL p)) wX wR
forall wX wY. FL p wX wY -> FL (PrimOf (FL p)) wX wY
forall (p :: * -> * -> *) wX wY.
Effect p =>
p wX wY -> FL (PrimOf p) wX wY
effect (PatchInfoAnd p wX wR -> Named p wX wR
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> p wA wB
hopefully PatchInfoAnd p wX wR
oldp))
              FL (PrimOf p) wR wY
chs
          let fixups :: FL (RebaseFixup (PrimOf p)) wY wZ
fixups =
                (forall wW wY. PrimOf p wW wY -> RebaseFixup (PrimOf p) wW wY)
-> FL (PrimOf p) wY wR -> FL (RebaseFixup (PrimOf p)) wY wR
forall (a :: * -> * -> *) (b :: * -> * -> *) wX wZ.
(forall wW wY. a wW wY -> b wW wY) -> FL a wX wZ -> FL b wX wZ
mapFL_FL PrimOf p wW wY -> RebaseFixup (PrimOf p) wW wY
forall wW wY. PrimOf p wW wY -> RebaseFixup (PrimOf p) wW wY
forall (prim :: * -> * -> *) wX wY.
prim wX wY -> RebaseFixup prim wX wY
PrimFixup (FL (PrimOf p) wR wY -> FL (PrimOf p) wY wR
forall wX wY. FL (PrimOf p) wX wY -> FL (PrimOf p) wY wX
forall (p :: * -> * -> *) wX wY. Invert p => p wX wY -> p wY wX
invert FL (PrimOf p) wR wY
chs) FL (RebaseFixup (PrimOf p)) wY wR
-> FL (RebaseFixup (PrimOf p)) wR wZ
-> FL (RebaseFixup (PrimOf p)) wY wZ
forall (a :: * -> * -> *) wX wY wZ.
FL a wX wY -> FL a wY wZ -> FL a wX wZ
+>+
                RebaseName wR wZ -> RebaseFixup (PrimOf p) wR wZ
forall wX wY (prim :: * -> * -> *).
RebaseName wX wY -> RebaseFixup prim wX wY
NameFixup (PatchInfo -> PatchInfo -> RebaseName wR wZ
forall wX wY. PatchInfo -> PatchInfo -> RebaseName wX wY
Rename (PatchInfoAnd p wX wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAnd p wX wY
newp) (PatchInfoAnd p wX wR -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAnd p wX wR
oldp)) RebaseFixup (PrimOf p) wR wZ
-> FL (RebaseFixup (PrimOf p)) wZ wZ
-> FL (RebaseFixup (PrimOf p)) wR wZ
forall (a :: * -> * -> *) wX wY wZ.
a wX wY -> FL a wY wZ -> FL a wX wZ
:>:
                FL (RebaseFixup (PrimOf p)) wZ wZ
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL
          PatchInfoAnd p wX wY -> IO ()
forall (p :: * -> * -> *) wX wY. PatchInspect p => p wX wY -> IO ()
setEnvDarcsFiles PatchInfoAnd p wX wY
newp
          Repository 'RW p wU wY
_repository <-
            Repository 'RW p wU wX
-> UpdatePending
-> PatchInfoAnd p wX wY
-> IO (Repository 'RW p wU wY)
forall (p :: * -> * -> *) wU wR wY.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RW p wU wR
-> UpdatePending
-> PatchInfoAnd p wR wY
-> IO (Repository 'RW p wU wY)
tentativelyAddPatch Repository 'RW p wU wX
_repository UpdatePending
NoUpdatePending PatchInfoAnd p wX wY
newp
          (Repository 'RW p wU wY, FL (RebaseFixup (PrimOf p)) wY wR,
 (Maybe String, PatchInfoAnd p wX wY))
-> IO
     (Repository 'RW p wU wY, FL (RebaseFixup (PrimOf p)) wY wR,
      (Maybe String, PatchInfoAnd p wX wY))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Repository 'RW p wU wY
_repository, FL (RebaseFixup (PrimOf p)) wY wR
forall {wZ}. FL (RebaseFixup (PrimOf p)) wY wZ
fixups, (Maybe String
mlogf, PatchInfoAnd p wX wY
newp))
      let failmsg :: String
failmsg = String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (\String
lf -> String
"\nLogfile left in " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
lf String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".") Maybe String
mlogf
      Tree IO
tp <- Repository 'RW p wU wY -> IO (Tree IO)
forall (rt :: AccessType) (p :: * -> * -> *) wU wR.
Repository rt p wU wR -> IO (Tree IO)
readPristine Repository 'RW p wU wY
_repository
      Tree IO -> [DarcsFlag] -> String -> String -> Maybe String -> IO ()
testTentativeAndMaybeExit Tree IO
tp [DarcsFlag]
cfg
        (String
"you have a bad patch: '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ PatchInfoAnd p wX wY -> String
forall (p :: * -> * -> *) wX wY. PatchInfoAnd p wX wY -> String
patchDesc PatchInfoAnd p wX wY
newp String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'")
        String
"amend it"
        (String -> Maybe String
forall a. a -> Maybe a
Just String
failmsg)
      if PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.amendUnrecord PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg then
        Repository 'RW p wU wY -> FL (PrimOf p) wY wX -> IO ()
forall (p :: * -> * -> *) wU wR wP.
RepoPatch p =>
Repository 'RW p wU wR -> FL (PrimOf p) wR wP -> IO ()
writeTentativePending Repository 'RW p wU wY
_repository (FL (PrimOf p) wY wX -> IO ()) -> FL (PrimOf p) wY wX -> IO ()
forall a b. (a -> b) -> a -> b
$ FL (PrimOf p) wR wY -> FL (PrimOf p) wY wR
forall wX wY. FL (PrimOf p) wX wY -> FL (PrimOf p) wY wX
forall (p :: * -> * -> *) wX wY. Invert p => p wX wY -> p wY wX
invert FL (PrimOf p) wR wY
chs FL (PrimOf p) wY wR -> FL (PrimOf p) wR wX -> FL (PrimOf p) wY wX
forall (a :: * -> * -> *) wX wY wZ.
FL a wX wY -> FL a wY wZ -> FL a wX wZ
+>+ FL (PrimOf p) wR wX
old_pending
      else
        Repository 'RW p wU wY
-> FL (PrimOf p) wR wY
-> FL (PrimOf p) wR wP
-> FL (PrimOf p) wP wU
-> IO ()
forall (p :: * -> * -> *) wR wO wP wU.
RepoPatch p =>
Repository 'RW p wU wR
-> FL (PrimOf p) wO wR
-> FL (PrimOf p) wO wP
-> FL (PrimOf p) wP wU
-> IO ()
tentativelyRemoveFromPW Repository 'RW p wU wY
_repository FL (PrimOf p) wR wY
chs FL (PrimOf p) wR wP
pending FL (PrimOf p) wP wU
working
      Repository 'RO p wU wY
_repository <-
        Repository 'RW p wU wY -> DryRun -> IO (Repository 'RO p wU wY)
forall (p :: * -> * -> *) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository 'RW p wU wR -> DryRun -> IO (Repository 'RO p wU wR)
finalizeRepositoryChanges Repository 'RW p wU wY
_repository (PrimOptSpec DarcsOptDescr DarcsFlag a DryRun
PrimDarcsOption DryRun
O.dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg)
          IO (Repository 'RO p wU wY)
-> String -> IO (Repository 'RO p wU wY)
forall a. IO a -> String -> IO a
`clarifyErrors` String
failmsg
      case PrimOptSpec DarcsOptDescr DarcsFlag a Verbosity
PrimDarcsOption Verbosity
O.verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg of
        Verbosity
O.NormalVerbosity -> Doc -> IO ()
putDocLn Doc
"Finished amending patch."
        Verbosity
O.Verbose -> Doc -> IO ()
putDocLn (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc
"Finished amending patch:" Doc -> Doc -> Doc
$$ PatchInfoAnd p wX wY -> Doc
forall wX wY. PatchInfoAndG (Named p) wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description PatchInfoAnd p wX wY
newp
        Verbosity
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      FL (PatchInfoAnd p) wX wY -> IO ()
forall (p :: * -> * -> *) wX wY.
RepoPatch p =>
FL (PatchInfoAnd p) wX wY -> IO ()
setEnvDarcsPatches (PatchInfoAnd p wX wY
newp PatchInfoAnd p wX wY
-> FL (PatchInfoAnd p) wY wY -> FL (PatchInfoAnd p) wX wY
forall (a :: * -> * -> *) wX wY wZ.
a wX wY -> FL a wY wZ -> FL a wX wZ
:>: FL (PatchInfoAnd p) wY wY
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL)

filterNotInRemote :: RepoPatch p
                  => Config
                  -> Repository 'RW p wU wR
                  -> PatchSet p Origin wR
                  -> IO ((PatchSet p :> RL (PatchInfoAnd p)) Origin wR)
filterNotInRemote :: forall (p :: * -> * -> *) wU wR.
RepoPatch p =>
[DarcsFlag]
-> Repository 'RW p wU wR
-> PatchSet p Origin wR
-> IO ((:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR)
filterNotInRemote [DarcsFlag]
cfg Repository 'RW p wU wR
repository PatchSet p Origin wR
patchSet = do
    [String]
nirs <- (NotInRemote -> IO String) -> [NotInRemote] -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM NotInRemote -> IO String
getNotInRemotePath (PrimOptSpec DarcsOptDescr DarcsFlag a [NotInRemote]
PrimDarcsOption [NotInRemote]
O.notInRemote PrimDarcsOption [NotInRemote] -> [DarcsFlag] -> [NotInRemote]
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg)
    if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
nirs
      then
        -- We call contextPatches here because
        -- (a) selecting patches beyond the latest clean tag is impossible anyway
        -- (b) makes it easier to reconstruct a PatchSet w/o the selected patch
        -- (c) avoids listing the complete list of patches in the repo when user
        --     rejects the last selectable patch
        (:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR
-> IO ((:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PatchSet p Origin wR
-> (:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR
forall (p :: * -> * -> *) wX wY.
PatchSet p wX wY -> (:>) (PatchSet p) (RL (PatchInfoAnd p)) wX wY
contextPatches PatchSet p Origin wR
patchSet)
      else do
        [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
cfg (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$
          Doc
"Determining patches not in" Doc -> Doc -> Doc
<+> [String] -> Doc
anyOfClause [String]
nirs Doc -> Doc -> Doc
$$ Int -> [String] -> Doc
itemizeVertical Int
2 [String]
nirs
        Sealed PatchSet p Origin wX
thems <- [Sealed (PatchSet p Origin)] -> Sealed (PatchSet p Origin)
forall (p :: * -> * -> *).
(Commute p, Merge p) =>
[SealedPatchSet p Origin] -> SealedPatchSet p Origin
patchSetUnion ([Sealed (PatchSet p Origin)] -> Sealed (PatchSet p Origin))
-> IO [Sealed (PatchSet p Origin)]
-> IO (Sealed (PatchSet p Origin))
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (String -> IO (Sealed (PatchSet p Origin)))
-> [String] -> IO [Sealed (PatchSet p Origin)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO (Sealed (PatchSet p Origin))
readNir [String]
nirs
        PatchSet p Origin wZ
in_remote :> FL (PatchInfoAnd p) wZ wR
only_ours <- (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wR
-> IO ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wR)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wR
 -> IO ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wR))
-> (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wR
-> IO ((:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wR)
forall a b. (a -> b) -> a -> b
$ PatchSet p Origin wR
-> PatchSet p Origin wX
-> (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wR
forall (p :: * -> * -> *) wX wY.
Commute p =>
PatchSet p Origin wX
-> PatchSet p Origin wY
-> (:>) (PatchSet p) (FL (PatchInfoAnd p)) Origin wX
findCommonWithThem PatchSet p Origin wR
patchSet PatchSet p Origin wX
thems
        (:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR
-> IO ((:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PatchSet p Origin wZ
in_remote PatchSet p Origin wZ
-> RL (PatchInfoAnd p) wZ wR
-> (:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR
forall (a1 :: * -> * -> *) (a2 :: * -> * -> *) wX wY wZ.
a1 wX wZ -> a2 wZ wY -> (:>) a1 a2 wX wY
:> FL (PatchInfoAnd p) wZ wR -> RL (PatchInfoAnd p) wZ wR
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> RL a wX wZ
reverseFL FL (PatchInfoAnd p) wZ wR
only_ours)
  where
    readNir :: String -> IO (Sealed (PatchSet p Origin))
readNir String
loc = do
      Repository 'RO p Any Any
repo <- ReadingOrWriting
-> Repository 'RW p wU wR
-> UseCache
-> String
-> IO (Repository 'RO p Any Any)
forall (rt :: AccessType) (p :: * -> * -> *) wU wR vR vU.
ReadingOrWriting
-> Repository rt p wU wR
-> UseCache
-> String
-> IO (Repository 'RO p vR vU)
identifyRepositoryFor ReadingOrWriting
Reading Repository 'RW p wU wR
repository (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
O.useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg) String
loc
      PatchSet p Origin Any
rps <- Repository 'RO p Any Any -> IO (PatchSet p Origin Any)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p Any Any
repo
      Sealed (PatchSet p Origin) -> IO (Sealed (PatchSet p Origin))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (PatchSet p Origin Any -> Sealed (PatchSet p Origin)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed PatchSet p Origin Any
rps)
    getNotInRemotePath :: NotInRemote -> IO String
getNotInRemotePath (O.NotInRemotePath String
p) = String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
p
    getNotInRemotePath NotInRemote
O.NotInDefaultRepo = do
        Maybe String
defaultRepo <- IO (Maybe String)
getDefaultRepo
        let err :: IO a
err = String -> IO a
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO a) -> String -> IO a
forall a b. (a -> b) -> a -> b
$ String
"No default push/pull repo configured, please pass a "
                         String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"repo name to --" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
O.notInRemoteFlagName
        IO String -> (String -> IO String) -> Maybe String -> IO String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO String
forall {a}. IO a
err String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
defaultRepo

hasEditMetadata :: Config -> Bool
hasEditMetadata :: [DarcsFlag] -> Bool
hasEditMetadata [DarcsFlag]
cfg = Maybe String -> Bool
forall a. Maybe a -> Bool
isJust (PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
PrimDarcsOption (Maybe String)
O.author PrimDarcsOption (Maybe String) -> [DarcsFlag] -> Maybe String
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg)
                    Bool -> Bool -> Bool
|| PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.selectAuthor PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg
                    Bool -> Bool -> Bool
|| Maybe String -> Bool
forall a. Maybe a -> Bool
isJust (PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe String)
PrimDarcsOption (Maybe String)
O.patchname PrimDarcsOption (Maybe String) -> [DarcsFlag] -> Maybe String
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg)
                    Bool -> Bool -> Bool
|| PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe AskLongComment)
PrimDarcsOption (Maybe AskLongComment)
O.askLongComment PrimDarcsOption (Maybe AskLongComment)
-> [DarcsFlag] -> Maybe AskLongComment
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg Maybe AskLongComment -> Maybe AskLongComment -> Bool
forall a. Eq a => a -> a -> Bool
== AskLongComment -> Maybe AskLongComment
forall a. a -> Maybe a
Just AskLongComment
O.YesEditLongComment
                    Bool -> Bool -> Bool
|| PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe AskLongComment)
PrimDarcsOption (Maybe AskLongComment)
O.askLongComment PrimDarcsOption (Maybe AskLongComment)
-> [DarcsFlag] -> Maybe AskLongComment
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg Maybe AskLongComment -> Maybe AskLongComment -> Bool
forall a. Eq a => a -> a -> Bool
== AskLongComment -> Maybe AskLongComment
forall a. a -> Maybe a
Just AskLongComment
O.PromptLongComment
                    Bool -> Bool -> Bool
|| PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.askDeps PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg

patchSelOpts :: Config -> S.PatchSelectionOptions
patchSelOpts :: [DarcsFlag] -> PatchSelectionOptions
patchSelOpts [DarcsFlag]
cfg = S.PatchSelectionOptions
    { verbosity :: Verbosity
S.verbosity = PrimOptSpec DarcsOptDescr DarcsFlag a Verbosity
PrimDarcsOption Verbosity
O.verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg
    , matchFlags :: [MatchFlag]
S.matchFlags = PrimOptSpec DarcsOptDescr DarcsFlag a [MatchFlag]
MatchOption
O.matchOneNontag MatchOption -> [DarcsFlag] -> [MatchFlag]
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg
    , interactive :: Bool
S.interactive = [DarcsFlag] -> Bool
isInteractive [DarcsFlag]
cfg
    , selectDeps :: SelectDeps
S.selectDeps = SelectDeps
O.PromptDeps -- option not supported, use default
    , withSummary :: WithSummary
S.withSummary = WithSummary
O.NoSummary -- option not supported, use default
    }

isInteractive :: Config -> Bool
isInteractive :: [DarcsFlag] -> Bool
isInteractive [DarcsFlag]
cfg = Bool -> (Bool -> Bool) -> Maybe Bool -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True Bool -> Bool
forall a. a -> a
id (PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe Bool)
PrimDarcsOption (Maybe Bool)
O.interactive PrimDarcsOption (Maybe Bool) -> [DarcsFlag] -> Maybe Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg)

putInfo :: Config -> Doc -> IO ()
putInfo :: [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
cfg Doc
what = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (PrimOptSpec DarcsOptDescr DarcsFlag a Verbosity
PrimDarcsOption Verbosity
O.verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
cfg Verbosity -> Verbosity -> Bool
forall a. Eq a => a -> a -> Bool
== Verbosity
O.Quiet) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Doc -> IO ()
putDocLn Doc
what