--  Copyright (C) 2002-2004 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 CPP, OverloadedStrings #-}

module Darcs.UI.Commands.Send ( send ) where

import Darcs.Prelude

import System.Directory ( renameFile )
import System.Exit
    ( exitSuccess
#ifndef HAVE_MAPI
    , ExitCode ( ExitFailure )
    , exitWith
#endif
    )
import System.IO ( hClose )
import Control.Exception ( catch, IOException, onException )
import Control.Monad ( when, unless, forM_ )
import Darcs.Util.Tree ( Tree )
import Data.List ( intercalate, isPrefixOf )
import Data.List ( stripPrefix )
import Data.Maybe ( isNothing, fromMaybe )

import Darcs.UI.Commands
    ( DarcsCommand(..), withStdOpts
    , putInfo
    , putVerbose
    , setEnvDarcsPatches
    , defaultRepo
    , amInHashedRepository
    )
import Darcs.UI.Commands.Clone ( otherHelpInheritDefault )
import Darcs.UI.Commands.Util ( printDryRunMessageAndExit, checkUnrelatedRepos )
import Darcs.UI.Flags
    ( DarcsFlag
    , willRemoveLogFile, changesReverse, dryRun, useCache, remoteRepos, setDefault
    , fixUrl
    , getCc
    , getAuthor
    , getSubject
    , getInReplyTo
    , getSendmailCmd
    , getOutput
    , charset
    , verbosity
    , isInteractive
    , author
    , hasLogfile
    , selectDeps
    , minimize
    , editDescription
    )
import Darcs.UI.Options
    ( (^), odesc, ocheck
    , defaultFlags, parseFlags, (?)
    )
import qualified Darcs.UI.Options.All as O

import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, hopefully, patchDesc )
import Darcs.Repository
    ( Repository
    , repoLocation
    , PatchSet
    , identifyRepositoryFor
    , ReadingOrWriting(..)
    , withRepository
    , RepoJob(..)
    , readRepo
    , readRecorded
    , prefsUrl )
import Darcs.Patch.Set ( Origin )
import Darcs.Patch.Apply( ApplyState )
import Darcs.Patch ( IsRepoType, RepoPatch, description, applyToTree, effect, invert )
import Darcs.Patch.Witnesses.Sealed ( Sealed(..) )
import Darcs.Patch.Witnesses.Unsafe ( unsafeCoerceP )
import Darcs.Patch.Witnesses.Ordered
    ( FL(..), (:>)(..), (:\/:)(..),
    mapFL, mapFL_FL, lengthFL, nullFL )
import Darcs.Patch.Bundle
    ( makeBundle
    , minContext
    , readContextFile
    )
import Darcs.Repository.Prefs ( addRepoSource, getPreflist )
import Darcs.Repository.Flags ( DryRun(..) )
import Darcs.Util.External ( fetchFilePS, Cachable(..) )
import Darcs.UI.External
    ( signString
    , sendEmailDoc
    , generateEmail
    , editFile
    , getSystemEncoding
    , isUTF8Locale
#ifndef HAVE_MAPI
    , haveSendmail
#endif
    )
import Darcs.Util.ByteString ( mmapFilePS, isAscii )
import qualified Data.ByteString.Char8 as BC (unpack)
import Darcs.Util.Lock
    ( withOpenTemp
    , writeDocBinFile
    , readDocBinFile
    , removeFileMayNotExist
    )
import Darcs.UI.SelectChanges
    ( WhichChanges(..)
    , selectionConfig
    , runSelection
    )
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions(..) )
import Darcs.Patch.Depends ( findCommonWithThem )
import Darcs.Util.Prompt ( askUser, promptYorn )
import Data.Text.Encoding       ( decodeUtf8' )
import Darcs.Util.Progress ( debugMessage )
import Darcs.UI.Email ( makeEmail )
import Darcs.UI.Completion ( prefArgs )
import Darcs.UI.Commands.Util ( getUniqueDPatchName )
import Darcs.Util.Printer
    ( Doc, formatWords, vsep, text, ($$), (<+>), putDoc, putDocLn
    , quoted, renderPS, sentence, vcat
    )
import Darcs.Util.English ( englishNum, Noun(..) )
import Darcs.Util.Exception ( catchall )
import Darcs.Util.Path ( FilePathLike, toFilePath, AbsolutePath, AbsolutePathOrStd,
                        getCurrentDirectory, useAbsoluteOrStd, makeAbsoluteOrStd )
import Darcs.Util.HTTP ( postUrl )
import Darcs.Util.Global ( darcsSendMessage, darcsSendMessageFinal )
import Darcs.Util.SignalHandler ( catchInterrupt )

patchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
patchSelOpts :: [DarcsFlag] -> PatchSelectionOptions
patchSelOpts [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 = (forall a. PrimOptSpec DarcsOptDescr DarcsFlag a [MatchFlag])
-> [DarcsFlag] -> [MatchFlag]
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags forall a. PrimOptSpec DarcsOptDescr DarcsFlag a [MatchFlag]
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 = WithContext
O.NoContext
    }

send :: DarcsCommand
send :: DarcsCommand
send = 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
"send"
    , commandHelp :: Doc
commandHelp = Doc
cmdHelp
    , commandDescription :: String
commandDescription = String
cmdDescription
    , commandExtraArgs :: Int
commandExtraArgs = Int
1
    , commandExtraArgHelp :: [String]
commandExtraArgHelp = [String
"[REPOSITORY]"]
    , commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
commandCommand = (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
sendCmd
    , 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
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> Any)
-> [DarcsOptDescr DarcsFlag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> Any)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> a)
sendAdvancedOpts
    , commandBasicOptions :: [DarcsOptDescr DarcsFlag]
commandBasicOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Any)
-> [DarcsOptDescr DarcsFlag]
forall (d :: * -> *) f a b. OptSpec d f a b -> [d f]
odesc OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Any)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
sendBasicOpts
    , commandDefaults :: [DarcsFlag]
commandDefaults = OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
-> [DarcsFlag]
forall (d :: * -> *) f b. OptSpec d f [f] b -> [f]
defaultFlags OptSpec
  DarcsOptDescr
  DarcsFlag
  [DarcsFlag]
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> [DarcsFlag])
forall a.
DarcsOption
  a
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
sendOpts
    , commandCheckOptions :: [DarcsFlag] -> [String]
commandCheckOptions = OptSpec
  DarcsOptDescr
  DarcsFlag
  Any
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> 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]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> Any)
forall a.
DarcsOption
  a
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
sendOpts
    }
  where
    sendBasicOpts :: OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
sendBasicOpts
      = PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  [MatchFlag]
forall a. PrimOptSpec DarcsOptDescr DarcsFlag a [MatchFlag]
O.matchSeveral
      PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  [MatchFlag]
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption SelectDeps
O.selectDeps
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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
  (HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption (Maybe Bool)
O.interactive -- True
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption HeaderFields
O.headerFields
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption (Maybe String)
O.author
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     ((Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     ((Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption (Maybe String)
O.charset
      OptSpec
  DarcsOptDescr
  DarcsFlag
  ((Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ((Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ((Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption (Bool, Maybe String)
O.sendmail
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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
  (Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption (Maybe Output)
O.output
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption Sign
O.sign
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
forall a. DarcsOption a (DryRun -> XmlOutput -> a)
O.dryRunXml
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     (WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  (WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption WithSummary
O.withSummary
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool -> InheritDefault -> Maybe String -> Bool -> Bool -> a)
     (Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe Bool -> InheritDefault -> Maybe String -> Bool -> Bool -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 -> Bool -> a)
  (Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
PrimDarcsOption Bool
O.editDescription
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe Bool -> InheritDefault -> Maybe String -> Bool -> Bool -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (InheritDefault -> Maybe String -> Bool -> Bool -> a)
     (Maybe Bool -> InheritDefault -> Maybe String -> Bool -> Bool -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (InheritDefault -> Maybe String -> Bool -> Bool -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 -> Bool -> a)
  (Maybe Bool -> InheritDefault -> Maybe String -> Bool -> Bool -> a)
PrimDarcsOption (Maybe Bool)
O.setDefault
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (InheritDefault -> Maybe String -> Bool -> Bool -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String -> Bool -> Bool -> a)
     (InheritDefault -> Maybe String -> Bool -> Bool -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe String -> Bool -> Bool -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 -> Bool -> a)
  (InheritDefault -> Maybe String -> Bool -> Bool -> a)
PrimDarcsOption InheritDefault
O.inheritDefault
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe String -> Bool -> Bool -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool -> Bool -> a)
     (Maybe String -> Bool -> Bool -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool -> Bool -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 -> Bool -> a)
  (Maybe String -> Bool -> Bool -> a)
PrimDarcsOption (Maybe String)
O.repoDir
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool -> Bool -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec DarcsOptDescr DarcsFlag (Bool -> a) (Bool -> Bool -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool -> a)
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 -> a) (Bool -> Bool -> a)
PrimDarcsOption Bool
O.minimize
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
-> OptSpec DarcsOptDescr DarcsFlag a (Bool -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     a
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> 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 (Bool -> a)
PrimDarcsOption Bool
O.allowUnrelatedRepos
    sendAdvancedOpts :: OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> a)
sendAdvancedOpts
      = PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (RemoteRepos -> Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
  Logfile
PrimDarcsOption Logfile
O.logfile
      PrimOptSpec
  DarcsOptDescr
  DarcsFlag
  (RemoteRepos -> Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
  Logfile
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
     (RemoteRepos -> Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
     (Logfile
      -> RemoteRepos
      -> Maybe AbsolutePath
      -> Bool
      -> 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
  (Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
  (RemoteRepos -> Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
PrimDarcsOption RemoteRepos
O.remoteRepos
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool -> NetworkOptions -> a)
     (Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (Bool -> NetworkOptions -> a)
     (Logfile
      -> RemoteRepos
      -> Maybe AbsolutePath
      -> Bool
      -> 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 -> NetworkOptions -> a)
  (Maybe AbsolutePath -> Bool -> NetworkOptions -> a)
PrimDarcsOption (Maybe AbsolutePath)
O.sendToContext 
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (Bool -> NetworkOptions -> a)
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (NetworkOptions -> a)
     (Bool -> NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     (NetworkOptions -> a)
     (Logfile
      -> RemoteRepos
      -> Maybe AbsolutePath
      -> Bool
      -> 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)
  (Bool -> NetworkOptions -> a)
PrimDarcsOption Bool
O.changesReverse
      OptSpec
  DarcsOptDescr
  DarcsFlag
  (NetworkOptions -> a)
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> a)
-> OptSpec DarcsOptDescr DarcsFlag a (NetworkOptions -> a)
-> OptSpec
     DarcsOptDescr
     DarcsFlag
     a
     (Logfile
      -> RemoteRepos
      -> Maybe AbsolutePath
      -> Bool
      -> 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
    sendOpts :: DarcsOption
  a
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
sendOpts = OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> a)
sendBasicOpts OptSpec
  DarcsOptDescr
  DarcsFlag
  (Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
  ([MatchFlag]
   -> SelectDeps
   -> Maybe Bool
   -> HeaderFields
   -> Maybe String
   -> Maybe String
   -> (Bool, Maybe String)
   -> Maybe Output
   -> Sign
   -> DryRun
   -> XmlOutput
   -> WithSummary
   -> Bool
   -> Maybe Bool
   -> InheritDefault
   -> Maybe String
   -> Bool
   -> Bool
   -> Maybe StdCmdAction
   -> Verbosity
   -> Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
-> DarcsOption
     (UseCache -> HooksConfig -> Bool -> Bool -> Bool -> a)
     (Logfile
      -> RemoteRepos
      -> Maybe AbsolutePath
      -> Bool
      -> NetworkOptions
      -> UseCache
      -> HooksConfig
      -> Bool
      -> Bool
      -> Bool
      -> a)
-> DarcsOption
     a
     ([MatchFlag]
      -> SelectDeps
      -> Maybe Bool
      -> HeaderFields
      -> Maybe String
      -> Maybe String
      -> (Bool, Maybe String)
      -> Maybe Output
      -> Sign
      -> DryRun
      -> XmlOutput
      -> WithSummary
      -> Bool
      -> Maybe Bool
      -> InheritDefault
      -> Maybe String
      -> Bool
      -> Bool
      -> Maybe StdCmdAction
      -> Verbosity
      -> Logfile
      -> RemoteRepos
      -> Maybe AbsolutePath
      -> Bool
      -> 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)
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> UseCache
   -> HooksConfig
   -> Bool
   -> Bool
   -> Bool
   -> a)
forall a.
OptSpec
  DarcsOptDescr
  DarcsFlag
  a
  (Logfile
   -> RemoteRepos
   -> Maybe AbsolutePath
   -> Bool
   -> NetworkOptions
   -> a)
sendAdvancedOpts

sendCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
sendCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
sendCmd (AbsolutePath, AbsolutePath)
fps [DarcsFlag]
opts [String
""] = (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
sendCmd (AbsolutePath, AbsolutePath)
fps [DarcsFlag]
opts []
sendCmd (AbsolutePath
_,AbsolutePath
o) [DarcsFlag]
opts [String
unfixedrepodir] =
 UseCache -> RepoJob () -> IO ()
forall a. UseCache -> RepoJob a -> IO a
withRepository (PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
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
$
  \(Repository rt p wR wU wR
repository :: Repository rt p wR wU wR) -> do
  case PrimDarcsOption (Maybe AbsolutePath)
O.sendToContext PrimDarcsOption (Maybe AbsolutePath)
-> [DarcsFlag] -> Maybe AbsolutePath
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts of
    Just AbsolutePath
contextfile -> do
        [WhatToDo]
wtds <- [DarcsFlag] -> Maybe (Repository rt p wR wU wR) -> IO [WhatToDo]
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
[DarcsFlag] -> Maybe (Repository rt p wR wU wT) -> IO [WhatToDo]
decideOnBehavior [DarcsFlag]
opts (Maybe (Repository rt p wR wU wR)
forall a. Maybe a
Nothing :: Maybe (Repository rt p wR wU wR))
        PatchSet rt p Origin wR
ref <- 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
        Sealed PatchSet rt p Origin wX
them <- PatchSet rt p Origin wR
-> String -> IO (Sealed (PatchSet rt p Origin))
forall (p :: * -> * -> *) (rt :: RepoType) wX.
Commute p =>
PatchSet rt p Origin wX
-> String -> IO (SealedPatchSet rt p Origin)
readContextFile PatchSet rt p Origin wR
ref (AbsolutePath -> String
forall a. FilePathLike a => a -> String
toFilePath AbsolutePath
contextfile)
        Repository rt p wR wU wR
-> [DarcsFlag]
-> [WhatToDo]
-> String
-> PatchSet rt p Origin wX
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT wX.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wT
-> [DarcsFlag]
-> [WhatToDo]
-> String
-> PatchSet rt p Origin wX
-> IO ()
sendToThem Repository rt p wR wU wR
repository [DarcsFlag]
opts [WhatToDo]
wtds String
"CONTEXT" PatchSet rt p Origin wX
them
    Maybe AbsolutePath
Nothing -> do
        String
repodir <- AbsolutePath -> String -> IO String
fixUrl AbsolutePath
o String
unfixedrepodir
        -- Test to make sure we aren't trying to push to the current repo
        AbsolutePath
here <- IO AbsolutePath
getCurrentDirectory
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
repodir String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== AbsolutePath -> String
forall a. FilePathLike a => a -> String
toFilePath AbsolutePath
here) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
           String -> IO ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
cannotSendToSelf
        [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
repodir]) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
            [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts (String -> Doc
creatingPatch String
repodir)
        Repository rt p Any Any Any
repo <- ReadingOrWriting
-> Repository rt p wR wU wR
-> 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 wR
repository (PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) String
repodir
        PatchSet rt p Origin Any
them <- 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
repo
        String
-> DryRun
-> RemoteRepos
-> SetDefault
-> InheritDefault
-> Bool
-> IO ()
addRepoSource String
repodir (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)
        [WhatToDo]
wtds <- [DarcsFlag] -> Maybe (Repository rt p Any Any Any) -> IO [WhatToDo]
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
[DarcsFlag] -> Maybe (Repository rt p wR wU wT) -> IO [WhatToDo]
decideOnBehavior [DarcsFlag]
opts (Repository rt p Any Any Any -> Maybe (Repository rt p Any Any Any)
forall a. a -> Maybe a
Just Repository rt p Any Any Any
repo)
        Repository rt p wR wU wR
-> [DarcsFlag]
-> [WhatToDo]
-> String
-> PatchSet rt p Origin Any
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT wX.
(IsRepoType rt, RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wR wU wT
-> [DarcsFlag]
-> [WhatToDo]
-> String
-> PatchSet rt p Origin wX
-> IO ()
sendToThem Repository rt p wR wU wR
repository [DarcsFlag]
opts [WhatToDo]
wtds String
repodir PatchSet rt p Origin Any
them
sendCmd (AbsolutePath, AbsolutePath)
_ [DarcsFlag]
_ [String]
_ = String -> IO ()
forall a. HasCallStack => String -> a
error String
"impossible case"

sendToThem :: (IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
           => Repository rt p wR wU wT -> [DarcsFlag] -> [WhatToDo] -> String
           -> PatchSet rt p Origin wX -> IO ()
sendToThem :: Repository rt p wR wU wT
-> [DarcsFlag]
-> [WhatToDo]
-> String
-> PatchSet rt p Origin wX
-> IO ()
sendToThem Repository rt p wR wU wT
repo [DarcsFlag]
opts [WhatToDo]
wtds String
their_name PatchSet rt p Origin wX
them = do
#ifndef HAVE_MAPI
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Bool, Maybe String) -> Bool
forall a b. (a, b) -> a
fst (PrimDarcsOption (Bool, Maybe String)
O.sendmail PrimDarcsOption (Bool, Maybe String)
-> [DarcsFlag] -> (Bool, Maybe String)
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) Bool -> Bool -> Bool
&& PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts DryRun -> DryRun -> Bool
forall a. Eq a => a -> a -> Bool
== DryRun
O.NoDryRun) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    -- If --mail is used, check if the user has sendmail or
    -- provided a --sendmail-cmd
    Bool
sendmail <- IO Bool
haveSendmail
    String
sm_cmd <- [DarcsFlag] -> IO String
getSendmailCmd [DarcsFlag]
opts
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
sendmail Bool -> Bool -> Bool
&& String
sm_cmd String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"") (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts Doc
noWorkingSendmail
        ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (ExitCode -> IO ()) -> ExitCode -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> ExitCode
ExitFailure Int
1
#endif
  PatchSet rt p Origin wR
us <- Repository rt p wR wU wT -> 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 wT
repo
  PatchSet rt p Origin wZ
common :> FL (PatchInfoAnd rt p) wZ wR
us' <- (:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wR
-> IO ((:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wR)
forall (m :: * -> *) a. Monad m => a -> m a
return ((:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wR
 -> IO ((:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wR))
-> (:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wR
-> IO ((:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wR)
forall a b. (a -> b) -> a -> b
$ PatchSet rt p Origin wR
-> PatchSet rt p Origin wX
-> (:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wR
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
Commute p =>
PatchSet rt p Origin wX
-> PatchSet rt p Origin wY
-> (:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin wX
findCommonWithThem PatchSet rt p Origin wR
us PatchSet rt p Origin wX
them
  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
O.allowUnrelatedRepos PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) PatchSet rt p Origin wR
us PatchSet rt p Origin wX
them
  case FL (PatchInfoAnd rt p) wZ wR
us' of
      FL (PatchInfoAnd rt p) wZ wR
NilFL -> do [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts Doc
nothingSendable
                  IO ()
forall a. IO a
exitSuccess
      FL (PatchInfoAnd rt p) wZ wR
_     -> [DarcsFlag] -> Doc -> IO ()
putVerbose [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
selectionIs ((forall wW wZ. PatchInfoAnd rt p wW wZ -> Doc)
-> FL (PatchInfoAnd rt p) wZ 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) wZ wR
us')
  Tree IO
pristine <- Repository rt p wR wU wT -> IO (Tree IO)
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
Repository rt p wR wU wT -> IO (Tree IO)
readRecorded Repository rt p wR wU wT
repo
  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
"send" ([DarcsFlag] -> PatchSelectionOptions
patchSelOpts [DarcsFlag]
opts) Maybe (Splitter (PatchInfoAnd rt p))
forall a. Maybe a
Nothing Maybe [AnchoredPath]
forall a. Maybe a
Nothing
  (FL (PatchInfoAnd rt p) wZ wZ
to_be_sent :> FL (PatchInfoAnd rt p) wZ wR
_) <- FL (PatchInfoAnd rt p) wZ wR
-> SelectionConfig (PatchInfoAnd rt p)
-> IO
     ((:>) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wZ wR)
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) wZ wR
us' SelectionConfig (PatchInfoAnd rt p)
selection_config
  String
-> Verbosity
-> WithSummary
-> DryRun
-> XmlOutput
-> Bool
-> FL (PatchInfoAnd rt p) wZ wZ
-> IO ()
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
RepoPatch p =>
String
-> Verbosity
-> WithSummary
-> DryRun
-> XmlOutput
-> Bool
-> FL (PatchInfoAnd rt p) wX wY
-> IO ()
printDryRunMessageAndExit String
"send"
      (PrimDarcsOption Verbosity
verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
      (PrimDarcsOption WithSummary
O.withSummary PrimDarcsOption WithSummary -> [DarcsFlag] -> WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
      (PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
      XmlOutput
O.NoXml
      (Bool -> [DarcsFlag] -> Bool
isInteractive Bool
True [DarcsFlag]
opts)
      FL (PatchInfoAnd rt p) wZ wZ
to_be_sent
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (FL (PatchInfoAnd rt p) wZ wZ -> Bool
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Bool
nullFL FL (PatchInfoAnd rt p) wZ wZ
to_be_sent) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts Doc
selectionIsNull
      IO ()
forall a. IO a
exitSuccess
  FL (PatchInfoAnd rt p) wZ wZ -> IO ()
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
RepoPatch p =>
FL (PatchInfoAnd rt p) wX wY -> IO ()
setEnvDarcsPatches FL (PatchInfoAnd rt p) wZ wZ
to_be_sent

  let genFullBundle :: IO Doc
genFullBundle = [DarcsFlag]
-> PatchSet rt p Origin wZ
-> Either
     (FL (PatchInfoAnd rt p) wR wZ)
     (Tree IO,
      (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wZ)
-> IO Doc
forall (rt :: RepoType) (p :: * -> * -> *) wX wY wZ.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> PatchSet rt p Origin wZ
-> Either
     (FL (PatchInfoAnd rt p) wX wY)
     (Tree IO,
      (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wX wY)
-> IO Doc
prepareBundle [DarcsFlag]
opts PatchSet rt p Origin wZ
common  ((Tree IO,
 (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wZ)
-> Either
     (FL (PatchInfoAnd rt p) wR wZ)
     (Tree IO,
      (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wZ)
forall a b. b -> Either a b
Right (Tree IO
pristine, FL (PatchInfoAnd rt p) wZ wR
us'FL (PatchInfoAnd rt p) wZ wR
-> FL (PatchInfoAnd rt p) wZ wZ
-> (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wR wZ
forall (a1 :: * -> * -> *) (a2 :: * -> * -> *) wX wY wZ.
a1 wZ wX -> a2 wZ wY -> (:\/:) a1 a2 wX wY
:\/:FL (PatchInfoAnd rt p) wZ wZ
to_be_sent))
  Doc
bundle <- if Bool -> Bool
not (PrimDarcsOption Bool
minimize PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
             then IO Doc
genFullBundle
             else do [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts Doc
"Minimizing context, to send with full context hit ctrl-C..."
                     ( case PatchSet rt p Origin wZ
-> FL (PatchInfoAnd rt p) wZ wZ
-> Sealed ((:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) Origin)
forall (p :: * -> * -> *) (rt :: RepoType) wStart wB wC.
RepoPatch p =>
PatchSet rt p wStart wB
-> FL (PatchInfoAnd rt p) wB wC
-> Sealed ((:>) (PatchSet rt p) (FL (PatchInfoAnd rt p)) wStart)
minContext PatchSet rt p Origin wZ
common FL (PatchInfoAnd rt p) wZ wZ
to_be_sent of
                         Sealed (PatchSet rt p Origin wZ
common' :> FL (PatchInfoAnd rt p) wZ wX
to_be_sent') -> [DarcsFlag]
-> PatchSet rt p Origin wZ
-> Either
     (FL (PatchInfoAnd rt p) wZ wX)
     (Tree IO,
      (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wZ wX)
-> IO Doc
forall (rt :: RepoType) (p :: * -> * -> *) wX wY wZ.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> PatchSet rt p Origin wZ
-> Either
     (FL (PatchInfoAnd rt p) wX wY)
     (Tree IO,
      (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wX wY)
-> IO Doc
prepareBundle [DarcsFlag]
opts PatchSet rt p Origin wZ
common' (FL (PatchInfoAnd rt p) wZ wX
-> Either
     (FL (PatchInfoAnd rt p) wZ wX)
     (Tree IO,
      (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wZ wX)
forall a b. a -> Either a b
Left FL (PatchInfoAnd rt p) wZ wX
to_be_sent') )
                     IO Doc -> IO Doc -> IO Doc
forall a. IO a -> IO a -> IO a
`catchInterrupt` IO Doc
genFullBundle
  AbsolutePath
here   <- IO AbsolutePath
getCurrentDirectory
  let make_fname :: FL (PatchInfoAndG rt (Named p)) wX wZ -> IO String
make_fname (PatchInfoAndG rt (Named p) wX wY
tb:>:FL (PatchInfoAndG rt (Named p)) wY wZ
_) = String -> IO String
getUniqueDPatchName (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ PatchInfoAndG rt (Named p) wX wY -> String
forall (rt :: RepoType) (p :: * -> * -> *) wX wY.
PatchInfoAnd rt p wX wY -> String
patchDesc PatchInfoAndG rt (Named p) wX wY
tb
      make_fname FL (PatchInfoAndG rt (Named p)) wX wZ
_ = String -> IO String
forall a. HasCallStack => String -> a
error String
"impossible case"
  String
fname <- FL (PatchInfoAnd rt p) wZ wZ -> IO String
forall (rt :: RepoType) (p :: * -> * -> *) wX wZ.
FL (PatchInfoAndG rt (Named p)) wX wZ -> IO String
make_fname FL (PatchInfoAnd rt p) wZ wZ
to_be_sent
  let outname :: Maybe AbsolutePathOrStd
outname = case [DarcsFlag] -> String -> Maybe AbsolutePathOrStd
getOutput [DarcsFlag]
opts String
fname of
                    Just AbsolutePathOrStd
f  -> AbsolutePathOrStd -> Maybe AbsolutePathOrStd
forall a. a -> Maybe a
Just AbsolutePathOrStd
f
                    Maybe AbsolutePathOrStd
Nothing | (Bool, Maybe String) -> Bool
forall a b. (a, b) -> a
fst (PrimDarcsOption (Bool, Maybe String)
O.sendmail PrimDarcsOption (Bool, Maybe String)
-> [DarcsFlag] -> (Bool, Maybe String)
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) -> Maybe AbsolutePathOrStd
forall a. Maybe a
Nothing
                            | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ String
p | Post String
p <- [WhatToDo]
wtds] -> Maybe AbsolutePathOrStd
forall a. Maybe a
Nothing
                            | Bool
otherwise        -> AbsolutePathOrStd -> Maybe AbsolutePathOrStd
forall a. a -> Maybe a
Just (AbsolutePath -> String -> AbsolutePathOrStd
makeAbsoluteOrStd AbsolutePath
here String
fname)
  case Maybe AbsolutePathOrStd
outname of
    Just AbsolutePathOrStd
fname' -> [DarcsFlag]
-> FL (PatchInfoAnd rt p) wZ wZ
-> Doc
-> AbsolutePathOrStd
-> [WhatToDo]
-> String
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wX wY.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> FL (PatchInfoAnd rt p) wX wY
-> Doc
-> AbsolutePathOrStd
-> [WhatToDo]
-> String
-> IO ()
writeBundleToFile [DarcsFlag]
opts FL (PatchInfoAnd rt p) wZ wZ
to_be_sent Doc
bundle AbsolutePathOrStd
fname' [WhatToDo]
wtds String
their_name
    Maybe AbsolutePathOrStd
Nothing     -> [DarcsFlag]
-> FL (PatchInfoAnd rt p) wZ wZ
-> Doc
-> String
-> [WhatToDo]
-> String
-> IO ()
forall (rt :: RepoType) (p :: * -> * -> *) wX wY.
(RepoPatch p, ApplyState p ~ Tree) =>
[DarcsFlag]
-> FL (PatchInfoAnd rt p) wX wY
-> Doc
-> String
-> [WhatToDo]
-> String
-> IO ()
sendBundle [DarcsFlag]
opts FL (PatchInfoAnd rt p) wZ wZ
to_be_sent Doc
bundle String
fname [WhatToDo]
wtds String
their_name


prepareBundle :: forall rt p wX wY wZ. (RepoPatch p, ApplyState p ~ Tree)
              => [DarcsFlag] -> PatchSet rt p Origin wZ
              -> Either (FL (PatchInfoAnd rt p) wX wY)
                        (Tree IO, (FL (PatchInfoAnd rt p) :\/: FL (PatchInfoAnd rt p)) wX wY)
              -> IO Doc
prepareBundle :: [DarcsFlag]
-> PatchSet rt p Origin wZ
-> Either
     (FL (PatchInfoAnd rt p) wX wY)
     (Tree IO,
      (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wX wY)
-> IO Doc
prepareBundle [DarcsFlag]
opts PatchSet rt p Origin wZ
common Either
  (FL (PatchInfoAnd rt p) wX wY)
  (Tree IO,
   (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wX wY)
e = do
  Doc
unsig_bundle <-
     case Either
  (FL (PatchInfoAnd rt p) wX wY)
  (Tree IO,
   (:\/:) (FL (PatchInfoAnd rt p)) (FL (PatchInfoAnd rt p)) wX wY)
e of
       (Right (Tree IO
pristine, FL (PatchInfoAnd rt p) wZ wX
us' :\/: FL (PatchInfoAnd rt p) wZ wY
to_be_sent)) -> do
         Tree IO
pristine' <- FL (PrimOf p) wX wZ -> Tree IO -> IO (Tree IO)
forall (p :: * -> * -> *) (m :: * -> *) wX wY.
(Apply p, Monad m, ApplyState p ~ Tree) =>
p wX wY -> Tree m -> m (Tree m)
applyToTree (FL (PrimOf p) wZ wX -> FL (PrimOf p) wX wZ
forall (p :: * -> * -> *) wX wY. Invert p => p wX wY -> p wY wX
invert (FL (PrimOf p) wZ wX -> FL (PrimOf p) wX wZ)
-> FL (PrimOf p) wZ wX -> FL (PrimOf p) wX wZ
forall a b. (a -> b) -> a -> b
$ FL (PatchInfoAnd rt p) wZ wX
-> FL (PrimOf (FL (PatchInfoAnd rt p))) wZ wX
forall (p :: * -> * -> *) wX wY.
Effect p =>
p wX wY -> FL (PrimOf p) wX wY
effect FL (PatchInfoAnd rt p) wZ wX
us') Tree IO
pristine
         Maybe (Tree IO)
-> PatchSet rt p Any wZ -> FL (Named p) wZ wY -> 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
makeBundle (Tree IO -> Maybe (Tree IO)
forall a. a -> Maybe a
Just Tree IO
pristine')
                     (PatchSet rt p Origin wZ -> PatchSet rt p Any wZ
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP PatchSet rt p Origin wZ
common)
                     ((forall wW wY. PatchInfoAnd rt p wW wY -> Named p wW wY)
-> FL (PatchInfoAnd rt p) wZ wY -> FL (Named p) wZ wY
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) wZ wY
to_be_sent)
       Left FL (PatchInfoAnd rt p) wX wY
to_be_sent -> Maybe (Tree IO)
-> PatchSet rt p Any wX -> FL (Named p) wX wY -> 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
makeBundle Maybe (Tree IO)
forall a. Maybe a
Nothing
                                      (PatchSet rt p Origin wZ -> PatchSet rt p Any wX
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP PatchSet rt p Origin wZ
common)
                                      ((forall wW wY. PatchInfoAnd rt p wW wY -> Named p wW wY)
-> FL (PatchInfoAnd rt p) wX wY -> FL (Named p) wX wY
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) wX wY
to_be_sent)
  Sign -> Doc -> IO Doc
signString (PrimDarcsOption Sign -> [DarcsFlag] -> Sign
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimDarcsOption Sign
O.sign [DarcsFlag]
opts) Doc
unsig_bundle

sendBundle :: forall rt p wX wY . (RepoPatch p, ApplyState p ~ Tree)
           => [DarcsFlag] -> FL (PatchInfoAnd rt p) wX wY
             -> Doc -> String -> [WhatToDo] -> String -> IO ()
sendBundle :: [DarcsFlag]
-> FL (PatchInfoAnd rt p) wX wY
-> Doc
-> String
-> [WhatToDo]
-> String
-> IO ()
sendBundle [DarcsFlag]
opts FL (PatchInfoAnd rt p) wX wY
to_be_sent Doc
bundle String
fname [WhatToDo]
wtds String
their_name=
         let
           auto_subject :: forall pp wA wB . FL (PatchInfoAnd rt pp) wA wB -> String
           auto_subject :: FL (PatchInfoAnd rt pp) wA wB -> String
auto_subject (PatchInfoAnd rt pp wA wY
p:>:FL (PatchInfoAnd rt pp) wY wB
NilFL)  = String
"darcs patch: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> Int -> String
trim (PatchInfoAnd rt pp wA wY -> String
forall (rt :: RepoType) (p :: * -> * -> *) wX wY.
PatchInfoAnd rt p wX wY -> String
patchDesc PatchInfoAnd rt pp wA wY
p) Int
57
           auto_subject (PatchInfoAnd rt pp wA wY
p:>:FL (PatchInfoAnd rt pp) wY wB
ps) = String
"darcs patch: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> Int -> String
trim (PatchInfoAnd rt pp wA wY -> String
forall (rt :: RepoType) (p :: * -> * -> *) wX wY.
PatchInfoAnd rt p wX wY -> String
patchDesc PatchInfoAnd rt pp wA wY
p) Int
43 String -> String -> String
forall a. [a] -> [a] -> [a]
++
                            String
" (and " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (FL (PatchInfoAnd rt pp) wY wB -> Int
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Int
lengthFL FL (PatchInfoAnd rt pp) wY wB
ps) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" more)"
           auto_subject FL (PatchInfoAnd rt pp) wA wB
_ = String -> String
forall a. HasCallStack => String -> a
error String
"Tried to get a name from empty patch list."
           trim :: String -> Int -> String
trim String
st Int
n = if String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
st Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n then String
st
                       else Int -> String -> String
forall a. Int -> [a] -> [a]
take (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
3) String
st String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"..."
           in do
           [WhatToDo]
thetargets <- [WhatToDo] -> IO [WhatToDo]
getTargets [WhatToDo]
wtds
           String
from <- Maybe String -> Bool -> IO String
getAuthor (PrimDarcsOption (Maybe String)
author PrimDarcsOption (Maybe String) -> [DarcsFlag] -> Maybe String
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) Bool
False
           let thesubject :: String
thesubject = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe (FL (PatchInfoAnd rt p) wX wY -> String
forall (pp :: * -> * -> *) wA wB.
FL (PatchInfoAnd rt pp) wA wB -> String
auto_subject FL (PatchInfoAnd rt p) wX wY
to_be_sent) (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ [DarcsFlag] -> Maybe String
getSubject [DarcsFlag]
opts
           (Doc
mailcontents, Maybe String
mailfile, Maybe String
mailcharset) <- [DarcsFlag]
-> String
-> FL (PatchInfoAnd rt p) wX wY
-> IO (Doc, Maybe String, Maybe String)
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
RepoPatch p =>
[DarcsFlag]
-> String
-> FL (PatchInfoAnd rt p) wX wY
-> IO (Doc, Maybe String, Maybe String)
getDescription [DarcsFlag]
opts String
their_name FL (PatchInfoAnd rt p) wX wY
to_be_sent

           let warnMailBody :: IO ()
warnMailBody = case Maybe String
mailfile of
                                  Just String
mf -> Doc -> IO ()
putDocLn (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
emailBackedUp String
mf
                                  Maybe String
Nothing -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

               warnCharset :: String -> IO ()
warnCharset String
msg = do
                 Bool
confirmed <- String -> IO Bool
promptYorn (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ String -> String
promptCharSetWarning String
msg
                 Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
confirmed (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
                    Doc -> IO ()
putDocLn Doc
charsetAborted
                    IO ()
warnMailBody
                    IO ()
forall a. IO a
exitSuccess

           Maybe String
thecharset <- case PrimDarcsOption (Maybe String)
charset PrimDarcsOption (Maybe String) -> [DarcsFlag] -> Maybe String
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts of
                              -- Always trust provided charset
                              providedCset :: Maybe String
providedCset@(Just String
_) -> Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
providedCset
                              Maybe String
Nothing ->
                                case Maybe String
mailcharset of
                                Maybe String
Nothing -> do
                                  String -> IO ()
warnCharset String
charsetCouldNotGuess
                                  Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
mailcharset
                                Just String
"utf-8" -> do
                                  -- Check the locale encoding for consistency
                                  String
encoding <- IO String
getSystemEncoding
                                  String -> IO ()
debugMessage (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String
currentEncodingIs String
encoding
                                  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (String -> Bool
isUTF8Locale String
encoding) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                                    String -> IO ()
warnCharset String
charsetUtf8MailDiffLocale
                                  Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
mailcharset
                                -- Trust other cases (us-ascii)
                                Just String
_ -> Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
mailcharset

           let body :: Doc
body = String
-> [(String, String)]
-> Maybe Doc
-> Maybe String
-> Doc
-> Maybe String
-> Doc
makeEmail String
their_name
                        ([(String, String)]
-> (String -> [(String, String)])
-> Maybe String
-> [(String, String)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\String
x -> [(String
"In-Reply-To", String
x), (String
"References", String
x)]) (Maybe String -> [(String, String)])
-> ([DarcsFlag] -> Maybe String)
-> [DarcsFlag]
-> [(String, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [DarcsFlag] -> Maybe String
getInReplyTo ([DarcsFlag] -> [(String, String)])
-> [DarcsFlag] -> [(String, String)]
forall a b. (a -> b) -> a -> b
$ [DarcsFlag]
opts)
                        (Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
mailcontents)
                        Maybe String
thecharset
                        Doc
bundle
                        (String -> Maybe String
forall a. a -> Maybe a
Just String
fname)
               contentAndBundle :: Maybe (Doc, Doc)
contentAndBundle = (Doc, Doc) -> Maybe (Doc, Doc)
forall a. a -> Maybe a
Just (Doc
mailcontents, Doc
bundle)

               sendmail :: IO ()
sendmail =
                (do
                 String
sm_cmd <- [DarcsFlag] -> IO String
getSendmailCmd [DarcsFlag]
opts
                 let to :: String
to = [WhatToDo] -> String
generateEmailToString [WhatToDo]
thetargets
                 String
-> String
-> String
-> String
-> String
-> Maybe (Doc, Doc)
-> Doc
-> IO ()
sendEmailDoc String
from String
to String
thesubject ([DarcsFlag] -> String
getCc [DarcsFlag]
opts)
                               String
sm_cmd Maybe (Doc, Doc)
contentAndBundle Doc
body
                 [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts (String -> String -> Doc
success String
to ([DarcsFlag] -> String
getCc [DarcsFlag]
opts)))
                 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
`onException` IO ()
warnMailBody

           Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ String
p | Post String
p <- [WhatToDo]
thetargets]) IO ()
sendmail
           ByteString
nbody <- ((Handle, String) -> IO ByteString) -> IO ByteString
forall a. ((Handle, String) -> IO a) -> IO a
withOpenTemp (((Handle, String) -> IO ByteString) -> IO ByteString)
-> ((Handle, String) -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \ (Handle
fh,String
fn) -> do
               let to :: String
to = [WhatToDo] -> String
generateEmailToString [WhatToDo]
thetargets
               Handle -> String -> String -> String -> String -> Doc -> IO ()
generateEmail Handle
fh String
from String
to String
thesubject ([DarcsFlag] -> String
getCc [DarcsFlag]
opts) Doc
body
               Handle -> IO ()
hClose Handle
fh
               String -> IO ByteString
mmapFilePS String
fn
           [String] -> (String -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [ String
p | Post String
p <- [WhatToDo]
thetargets]
             (\String
url -> do
                [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Doc
postingPatch String
url
                String -> ByteString -> String -> IO ()
postUrl String
url ByteString
nbody String
"message/rfc822")
             IO () -> (IOException -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\(IOException
_ :: IOException) -> IO ()
sendmail)
           [DarcsFlag] -> Maybe String -> IO ()
forall t. FilePathLike t => [DarcsFlag] -> Maybe t -> IO ()
cleanup [DarcsFlag]
opts Maybe String
mailfile

generateEmailToString :: [WhatToDo] -> String
generateEmailToString :: [WhatToDo] -> String
generateEmailToString = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" , " ([String] -> String)
-> ([WhatToDo] -> [String]) -> [WhatToDo] -> 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
"") ([String] -> [String])
-> ([WhatToDo] -> [String]) -> [WhatToDo] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WhatToDo -> String) -> [WhatToDo] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map WhatToDo -> String
extractEmail
  where
    extractEmail :: WhatToDo -> String
extractEmail (SendMail String
t) = String
t
    extractEmail WhatToDo
_ = String
""

cleanup :: (FilePathLike t) => [DarcsFlag] -> Maybe t -> IO ()
cleanup :: [DarcsFlag] -> Maybe t -> IO ()
cleanup [DarcsFlag]
opts (Just t
mailfile) = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe AbsolutePath -> Bool
forall a. Maybe a -> Bool
isNothing ([DarcsFlag] -> Maybe AbsolutePath
hasLogfile [DarcsFlag]
opts) Bool -> Bool -> Bool
|| [DarcsFlag] -> Bool
willRemoveLogFile [DarcsFlag]
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                                      t -> IO ()
forall p. FilePathLike p => p -> IO ()
removeFileMayNotExist t
mailfile
cleanup [DarcsFlag]
_ Maybe t
Nothing = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

writeBundleToFile :: forall rt p wX wY . (RepoPatch p, ApplyState p ~ Tree)
                  => [DarcsFlag] -> FL (PatchInfoAnd rt p) wX wY -> Doc ->
                    AbsolutePathOrStd -> [WhatToDo] -> String -> IO ()
writeBundleToFile :: [DarcsFlag]
-> FL (PatchInfoAnd rt p) wX wY
-> Doc
-> AbsolutePathOrStd
-> [WhatToDo]
-> String
-> IO ()
writeBundleToFile [DarcsFlag]
opts FL (PatchInfoAnd rt p) wX wY
to_be_sent Doc
bundle AbsolutePathOrStd
fname [WhatToDo]
wtds String
their_name =
    do (Doc
d,Maybe String
f,Maybe String
_) <- [DarcsFlag]
-> String
-> FL (PatchInfoAnd rt p) wX wY
-> IO (Doc, Maybe String, Maybe String)
forall (p :: * -> * -> *) (rt :: RepoType) wX wY.
RepoPatch p =>
[DarcsFlag]
-> String
-> FL (PatchInfoAnd rt p) wX wY
-> IO (Doc, Maybe String, Maybe String)
getDescription [DarcsFlag]
opts String
their_name FL (PatchInfoAnd rt p) wX wY
to_be_sent
       let putabs :: a -> IO ()
putabs a
a = do a -> Doc -> IO ()
forall p. FilePathLike p => p -> Doc -> IO ()
writeDocBinFile a
a (Doc
d Doc -> Doc -> Doc
$$ Doc
bundle)
                         Doc -> IO ()
putDocLn (a -> Doc
forall a. FilePathLike a => a -> Doc
wroteBundle a
a)
           putstd :: IO ()
putstd = Doc -> IO ()
putDoc (Doc
d Doc -> Doc -> Doc
$$ Doc
bundle)
       (AbsolutePath -> IO ()) -> IO () -> AbsolutePathOrStd -> IO ()
forall a. (AbsolutePath -> a) -> a -> AbsolutePathOrStd -> a
useAbsoluteOrStd AbsolutePath -> IO ()
forall p. FilePathLike p => p -> IO ()
putabs IO ()
putstd AbsolutePathOrStd
fname
       let to :: String
to = [WhatToDo] -> String
generateEmailToString [WhatToDo]
wtds
       Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
to) (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
savedButNotSent String
to
       [DarcsFlag] -> Maybe String -> IO ()
forall t. FilePathLike t => [DarcsFlag] -> Maybe t -> IO ()
cleanup [DarcsFlag]
opts Maybe String
f

data WhatToDo
    = Post String        -- ^ POST the patch via HTTP
    | SendMail String    -- ^ send patch via email

decideOnBehavior :: [DarcsFlag] -> Maybe (Repository rt p wR wU wT) -> IO [WhatToDo]
decideOnBehavior :: [DarcsFlag] -> Maybe (Repository rt p wR wU wT) -> IO [WhatToDo]
decideOnBehavior [DarcsFlag]
opts Maybe (Repository rt p wR wU wT)
remote_repo =
    case [WhatToDo]
the_targets of
    [] -> do [WhatToDo]
wtds <- case Maybe (Repository rt p wR wU wT)
remote_repo of
                     Maybe (Repository rt p wR wU wT)
Nothing -> [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return []
                     Just Repository rt p wR wU wT
r -> Repository rt p wR wU wT -> IO [WhatToDo]
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
Repository rt p wR wU wT -> IO [WhatToDo]
check_post Repository rt p wR wU wT
r
             Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([WhatToDo] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [WhatToDo]
wtds) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ [WhatToDo] -> IO ()
announce_recipients [WhatToDo]
wtds
             [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return [WhatToDo]
wtds
    [WhatToDo]
ts -> do [WhatToDo] -> IO ()
announce_recipients [WhatToDo]
ts
             [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return [WhatToDo]
ts
    where the_targets :: [WhatToDo]
the_targets = [DarcsFlag] -> [WhatToDo]
collectTargets [DarcsFlag]
opts
          check_post :: Repository rt p wR wU wT -> IO [WhatToDo]
check_post Repository rt p wR wU wT
the_remote_repo =
                       do [WhatToDo]
p <- ((String -> [WhatToDo]
readPost (String -> [WhatToDo])
-> (ByteString -> String) -> ByteString -> [WhatToDo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
BC.unpack) (ByteString -> [WhatToDo]) -> IO ByteString -> IO [WhatToDo]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                                String -> Cachable -> IO ByteString
fetchFilePS (String -> String
prefsUrl (Repository rt p wR wU wT -> String
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
Repository rt p wR wU wT -> String
repoLocation Repository rt p wR wU wT
the_remote_repo) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/post")
                                (CInt -> Cachable
MaxAge CInt
600)) IO [WhatToDo] -> IO [WhatToDo] -> IO [WhatToDo]
forall a. IO a -> IO a -> IO a
`catchall` [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return []
                          [WhatToDo]
emails <- Repository rt p wR wU wT -> IO [WhatToDo]
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
Repository rt p wR wU wT -> IO [WhatToDo]
who_to_email Repository rt p wR wU wT
the_remote_repo
                          [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return ([WhatToDo]
p[WhatToDo] -> [WhatToDo] -> [WhatToDo]
forall a. [a] -> [a] -> [a]
++[WhatToDo]
emails)
          readPost :: String -> [WhatToDo]
readPost = (String -> WhatToDo) -> [String] -> [WhatToDo]
forall a b. (a -> b) -> [a] -> [b]
map String -> WhatToDo
parseLine ([String] -> [WhatToDo])
-> (String -> [String]) -> String -> [WhatToDo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines where
              parseLine :: String -> WhatToDo
parseLine String
t = WhatToDo -> (String -> WhatToDo) -> Maybe String -> WhatToDo
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> WhatToDo
Post String
t) String -> WhatToDo
SendMail (Maybe String -> WhatToDo) -> Maybe String -> WhatToDo
forall a b. (a -> b) -> a -> b
$ String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
"mailto:" String
t
          who_to_email :: Repository rt p wR wU wT -> IO [WhatToDo]
who_to_email Repository rt p wR wU wT
repo =
              do String
email <- (ByteString -> String
BC.unpack (ByteString -> String) -> IO ByteString -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                           String -> Cachable -> IO ByteString
fetchFilePS (String -> String
prefsUrl (Repository rt p wR wU wT -> String
forall (rt :: RepoType) (p :: * -> * -> *) wR wU wT.
Repository rt p wR wU wT -> String
repoLocation Repository rt p wR wU wT
repo) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/email")
                                       (CInt -> Cachable
MaxAge CInt
600))
                          IO String -> IO String -> IO String
forall a. IO a -> IO a -> IO a
`catchall` String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
                 if Char
'@' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
email then [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return ([WhatToDo] -> IO [WhatToDo])
-> ([String] -> [WhatToDo]) -> [String] -> IO [WhatToDo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> WhatToDo) -> [String] -> [WhatToDo]
forall a b. (a -> b) -> [a] -> [b]
map String -> WhatToDo
SendMail ([String] -> IO [WhatToDo]) -> [String] -> IO [WhatToDo]
forall a b. (a -> b) -> a -> b
$ String -> [String]
lines String
email
                                     else [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return []
          announce_recipients :: [WhatToDo] -> IO ()
announce_recipients [WhatToDo]
emails =
            let pn :: WhatToDo -> String
pn (SendMail String
s) = String
s
                pn (Post String
p) = String
p
                msg :: Doc
msg = DryRun -> [String] -> Doc
willSendTo (PrimDarcsOption DryRun
dryRun PrimDarcsOption DryRun -> [DarcsFlag] -> DryRun
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) ((WhatToDo -> String) -> [WhatToDo] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map WhatToDo -> String
pn [WhatToDo]
emails)
            in 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 -> [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts Doc
msg
                DryRun
O.NoDryRun  -> Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([WhatToDo] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [WhatToDo]
the_targets Bool -> Bool -> Bool
&& Maybe AbsolutePathOrStd -> Bool
forall a. Maybe a -> Bool
isNothing ([DarcsFlag] -> String -> Maybe AbsolutePathOrStd
getOutput [DarcsFlag]
opts String
"")) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                                [DarcsFlag] -> Doc -> IO ()
putInfo [DarcsFlag]
opts Doc
msg

getTargets :: [WhatToDo] -> IO [WhatToDo]
getTargets :: [WhatToDo] -> IO [WhatToDo]
getTargets [] = (String -> [WhatToDo]) -> IO String -> IO [WhatToDo]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((WhatToDo -> [WhatToDo] -> [WhatToDo]
forall a. a -> [a] -> [a]
:[]) (WhatToDo -> [WhatToDo])
-> (String -> WhatToDo) -> String -> [WhatToDo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> WhatToDo
SendMail) (IO String -> IO [WhatToDo]) -> IO String -> IO [WhatToDo]
forall a b. (a -> b) -> a -> b
$ String -> IO String
askUser String
promptTarget
getTargets [WhatToDo]
wtds = [WhatToDo] -> IO [WhatToDo]
forall (m :: * -> *) a. Monad m => a -> m a
return [WhatToDo]
wtds

collectTargets :: [DarcsFlag] -> [WhatToDo]
collectTargets :: [DarcsFlag] -> [WhatToDo]
collectTargets [DarcsFlag]
flags = [ String -> WhatToDo
f String
t | String
t <- HeaderFields -> [String]
O._to (PrimDarcsOption HeaderFields
O.headerFields PrimDarcsOption HeaderFields -> [DarcsFlag] -> HeaderFields
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags) ] where
    f :: String -> WhatToDo
f String
url | String
"http:" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
url = String -> WhatToDo
Post String
url
    f String
em = String -> WhatToDo
SendMail String
em

getDescription :: RepoPatch p
               => [DarcsFlag] -> String -> FL (PatchInfoAnd rt p) wX wY -> IO (Doc, Maybe String, Maybe String)
getDescription :: [DarcsFlag]
-> String
-> FL (PatchInfoAnd rt p) wX wY
-> IO (Doc, Maybe String, Maybe String)
getDescription [DarcsFlag]
opts String
their_name FL (PatchInfoAnd rt p) wX wY
patches =
    case Maybe String
get_filename of
        Just String
file -> do
                     Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (PrimDarcsOption Bool
editDescription PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
                       Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe AbsolutePath -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe AbsolutePath -> Bool) -> Maybe AbsolutePath -> Bool
forall a b. (a -> b) -> a -> b
$ [DarcsFlag] -> Maybe AbsolutePath
hasLogfile [DarcsFlag]
opts) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                            String -> Doc -> IO ()
forall p. FilePathLike p => p -> Doc -> IO ()
writeDocBinFile String
file Doc
patchdesc
                       String -> IO ()
debugMessage (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String
aboutToEdit String
file
                       (ExitCode
_, Bool
changed) <- String -> IO (ExitCode, Bool)
forall p. FilePathLike p => p -> IO (ExitCode, Bool)
editFile String
file
                       Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
changed (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
                         Bool
confirmed <- String -> IO Bool
promptYorn String
promptNoDescriptionChange
                         Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
confirmed (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do Doc -> IO ()
putDocLn Doc
aborted
                                               IO ()
forall a. IO a
exitSuccess
                       () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                     
                     String
updatedFile <- String -> IO String
updateFilename String
file
                     Doc
doc <- String -> IO Doc
forall p. FilePathLike p => p -> IO Doc
readDocBinFile String
updatedFile
                     
                     (Doc, Maybe String, Maybe String)
-> IO (Doc, Maybe String, Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc
doc, String -> Maybe String
forall a. a -> Maybe a
Just String
updatedFile, Doc -> Maybe String
forall a. IsString a => Doc -> Maybe a
tryGetCharset Doc
doc)
        Maybe String
Nothing -> (Doc, Maybe String, Maybe String)
-> IO (Doc, Maybe String, Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Doc
patchdesc, Maybe String
forall a. Maybe a
Nothing, Doc -> Maybe String
forall a. IsString a => Doc -> Maybe a
tryGetCharset Doc
patchdesc)
    where patchdesc :: Doc
patchdesc = String -> Doc
text (Int -> String
forall a. Show a => a -> String
show Int
len)
                      Doc -> Doc -> Doc
<+> String -> Doc
text (Int -> Noun -> String -> String
forall n. Countable n => Int -> n -> String -> String
englishNum Int
len (String -> Noun
Noun String
"patch") String
"")
                      Doc -> Doc -> Doc
<+> String -> Doc
text String
"for repository" Doc -> Doc -> Doc
<+> String -> Doc
text String
their_name Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text String
":"
                      Doc -> Doc -> Doc
$$ String -> Doc
text String
""
                      Doc -> Doc -> Doc
$$ [Doc] -> Doc
vsep ((forall wW wZ. PatchInfoAnd rt p wW wZ -> Doc)
-> FL (PatchInfoAnd rt p) wX wY -> [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) wX wY
patches)
            where
              len :: Int
len = FL (PatchInfoAnd rt p) wX wY -> Int
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> Int
lengthFL FL (PatchInfoAnd rt p) wX wY
patches
          updateFilename :: String -> IO String
updateFilename String
file = 
                IO String
-> (AbsolutePath -> IO String) -> Maybe AbsolutePath -> IO String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> String -> IO ()
renameFile String
file String
darcsSendMessageFinal IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                       String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
darcsSendMessageFinal) (String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String)
-> (AbsolutePath -> String) -> AbsolutePath -> IO String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AbsolutePath -> String
forall a. FilePathLike a => a -> String
toFilePath) (Maybe AbsolutePath -> IO String)
-> Maybe AbsolutePath -> IO String
forall a b. (a -> b) -> a -> b
$ [DarcsFlag] -> Maybe AbsolutePath
hasLogfile [DarcsFlag]
opts
          get_filename :: Maybe String
get_filename = case [DarcsFlag] -> Maybe AbsolutePath
hasLogfile [DarcsFlag]
opts of
                                Just AbsolutePath
f -> String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ AbsolutePath -> String
forall a. FilePathLike a => a -> String
toFilePath AbsolutePath
f
                                Maybe AbsolutePath
Nothing -> if PrimDarcsOption Bool
editDescription PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts
                                              then String -> Maybe String
forall a. a -> Maybe a
Just String
darcsSendMessage
                                              else Maybe String
forall a. Maybe a
Nothing
          tryGetCharset :: Doc -> Maybe a
tryGetCharset Doc
content = let body :: ByteString
body = Doc -> ByteString
renderPS Doc
content in
                                  if ByteString -> Bool
isAscii ByteString
body
                                  then a -> Maybe a
forall a. a -> Maybe a
Just a
"us-ascii"
                                  else (UnicodeException -> Maybe a)
-> (Text -> Maybe a) -> Either UnicodeException Text -> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> UnicodeException -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing)
                                              (Maybe a -> Text -> Maybe a
forall a b. a -> b -> a
const (Maybe a -> Text -> Maybe a) -> Maybe a -> Text -> Maybe a
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
"utf-8")
                                              (ByteString -> Either UnicodeException Text
decodeUtf8' ByteString
body)

cmdDescription :: String
cmdDescription :: String
cmdDescription =
    String
"Prepare a bundle of patches to be applied to some target repository."

cmdHelp :: Doc
cmdHelp :: Doc
cmdHelp = [Doc] -> Doc
vsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$
  ([String] -> Doc) -> [[String]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [String] -> Doc
formatWords
  [ [ String
"Send is used to prepare a bundle of patches that can be applied to a target"
    , String
"repository.  Send accepts the URL of the repository as an argument.  When"
    , String
"called without an argument, send will use the most recent repository that"
    , String
"was either pushed to, pulled from or sent to.  By default, the patch bundle"
    , String
"is saved to a file, although you may directly send it by mail."
    ]
  , [ String
"The `--output`, `--output-auto-name`, and `--to` flags determine"
    , String
"what darcs does with the patch bundle after creating it.  If you provide an"
    , String
"`--output` argument, the patch bundle is saved to that file.  If you"
    , String
"specify `--output-auto-name`, the patch bundle is saved to a file with an"
    , String
"automatically generated name.  If you give one or more `--to` arguments,"
    , String
"the bundle of patches is sent to those locations. The locations may either"
    , String
"be email addresses or urls that the patch should be submitted to via HTTP."
    ]
  , [ String
"If you provide the `--mail` flag, darcs will look at the contents"
    , String
"of the `_darcs/prefs/email` file in the target repository (if it exists),"
    , String
"and send the patch by email to that address.  In this case, you may use"
    , String
"the `--cc` option to specify additional recipients without overriding the"
    , String
"default repository email address."
    ]
  , [ String
"If `_darcs/prefs/post` exists in the target repository, darcs will"
    , String
"upload to the URL contained in that file, which may either be a"
    , String
"`mailto:` URL, or an `http://` URL.  In the latter case, the"
    , String
"patch is posted to that URL."
    ]
  , [ String
"If there is no email address associated with the repository, darcs will"
    , String
"prompt you for an email address."
    ]
  , [ String
"Use the `--subject` flag to set the subject of the e-mail to be sent."
    , String
"If you don't provide a subject on the command line, darcs will make one up"
    , String
"based on names of the patches in the patch bundle."
    ]
  , [ String
"Use the `--in-reply-to` flag to set the In-Reply-To and References headers"
    , String
"of the e-mail to be sent. By default no additional headers are included so"
    , String
"e-mail will not be treated as reply by mail readers."
    ]
  , [ String
"If you want to include a description or explanation along with the bundle"
    , String
"of patches, you need to specify the `--edit-description` flag, which"
    , String
"will cause darcs to open up an editor with which you can compose a message"
    , String
"to go along with your patches."
    ]
  , [ String
"If you want to use a command different from the default one for sending"
    , String
"email, you need to specify a command line with the `--sendmail-command`"
    , String
"option. The command line can contain some format specifiers which are"
    , String
"replaced by the actual values. Accepted format specifiers are `%s` for"
    , String
"subject, `%t` for to, `%c` for cc, `%b` for the body of the mail, `%f` for"
    , String
"from, `%a` for the patch bundle and the same specifiers in uppercase for the"
    , String
"URL-encoded values."
    , String
"Additionally you can add `%<` to the end of the command line if the command"
    , String
"expects the complete email message on standard input. E.g. the command lines"
    , String
"for evolution and msmtp look like this:"
    ]
  ]
  [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++
  -- TODO autoformatting for indented paragraphs
  [ [Doc] -> Doc
vcat
    [ Doc
"    evolution \"mailto:%T?subject=%S&attach=%A&cc=%C&body=%B\""
    , Doc
"    msmtp -t %<"
    ]
  ]
  [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ ([String] -> Doc) -> [[String]] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map [String] -> Doc
formatWords
  [ [ String
"Do not confuse the `--author` options with the return address"
    , String
"that `darcs send` will set for your patch bundle."
    ]
  , [ String
"For example, if you have two email addresses A and B:"
    ]
  ]
  [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++
  -- TODO autoformatting for bullet lists
  [ [Doc] -> Doc
vcat
    [ Doc
"  * If you use `--author A` but your machine is configured to send"
    , Doc
"    mail from address B by default, then the return address on your"
    , Doc
"    message will be B."
    , Doc
"  * If you use `--from A` and your mail client supports setting the"
    , Doc
"    From: address arbitrarily (some non-Unix-like mail clients,"
    , Doc
"    especially, may not support this), then the return address will"
    , Doc
"    be A; if it does not support this, then the return address will"
    , Doc
"    be B."
    , Doc
"  * If you supply neither `--from` nor `--author` then the return"
    , Doc
"    address will be B."
    ]
  ]
  [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++
  [ [String] -> Doc
formatWords
    [ String
"In addition, unless you specify the sendmail command with"
    , String
"`--sendmail-command`, darcs sends email using the default email"
    , String
"command on your computer. This default command is determined by the"
    , String
"`configure` script. Thus, on some non-Unix-like OSes,"
    , String
"`--from` is likely to not work at all."
    ]
  , Doc
otherHelpInheritDefault
  ]

cannotSendToSelf :: String
cannotSendToSelf :: String
cannotSendToSelf = String
"Can't send to current repository! Did you mean send --context?"

creatingPatch :: String -> Doc
creatingPatch :: String -> Doc
creatingPatch String
repodir = Doc
"Creating patch to" Doc -> Doc -> Doc
<+> String -> Doc
quoted String
repodir Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"..."

#ifndef HAVE_MAPI
noWorkingSendmail :: Doc
noWorkingSendmail :: Doc
noWorkingSendmail = Doc
"No working sendmail instance on your machine!"
#endif

nothingSendable :: Doc
nothingSendable :: Doc
nothingSendable = Doc
"No recorded local changes to send!"

selectionIs :: [Doc] -> Doc
selectionIs :: [Doc] -> Doc
selectionIs [Doc]
descs = String -> Doc
text String
"We have the following patches to send:" Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat [Doc]
descs

selectionIsNull :: Doc
selectionIsNull :: Doc
selectionIsNull = String -> Doc
text String
"You don't want to send any patches, and that's fine with me!"

emailBackedUp :: String -> Doc
emailBackedUp :: String -> Doc
emailBackedUp String
mf = Doc -> Doc
sentence (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
"Email body left in" Doc -> Doc -> Doc
<+> String -> Doc
text String
mf Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> Doc
"."

promptCharSetWarning :: String -> String
promptCharSetWarning :: String -> String
promptCharSetWarning String
msg = String
"Warning: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"  Send anyway?"

charsetAborted :: Doc
charsetAborted :: Doc
charsetAborted = Doc
"Aborted.  You can specify charset with the --charset option."

charsetCouldNotGuess :: String
charsetCouldNotGuess :: String
charsetCouldNotGuess = String
"darcs could not guess the charset of your mail."

currentEncodingIs :: String -> String
currentEncodingIs :: String -> String
currentEncodingIs String
e = String
"Current locale encoding: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
e

charsetUtf8MailDiffLocale :: String
charsetUtf8MailDiffLocale :: String
charsetUtf8MailDiffLocale = String
"your mail is valid UTF-8 but your locale differs."

aborted :: Doc
aborted :: Doc
aborted = Doc
"Aborted."

success :: String -> String -> Doc
success :: String -> String -> Doc
success String
to String
cc = Doc -> Doc
sentence (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$
    Doc
"Successfully sent patch bundle to:" Doc -> Doc -> Doc
<+> String -> Doc
text String
to Doc -> Doc -> Doc
<+> String -> Doc
copies String
cc
  where
    copies :: String -> Doc
copies String
"" = Doc
""
    copies String
x  = Doc
"and cc'ed" Doc -> Doc -> Doc
<+> String -> Doc
text String
x

postingPatch :: String -> Doc
postingPatch :: String -> Doc
postingPatch String
url = Doc
"Posting patch to" Doc -> Doc -> Doc
<+> String -> Doc
text String
url

wroteBundle :: FilePathLike a => a -> Doc
wroteBundle :: a -> Doc
wroteBundle a
a = Doc -> Doc
sentence (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
"Wrote patch to" Doc -> Doc -> Doc
<+> String -> Doc
text (a -> String
forall a. FilePathLike a => a -> String
toFilePath a
a)

savedButNotSent :: String -> Doc
savedButNotSent :: String -> Doc
savedButNotSent String
to =
        String -> Doc
text (String
"The usual recipent for this bundle is: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
to)
    Doc -> Doc -> Doc
$$  String -> Doc
text String
"To send it automatically, make sure sendmail is working,"
    Doc -> Doc -> Doc
<+> String -> Doc
text String
"and add 'send mail' to _darcs/prefs/defaults or"
    Doc -> Doc -> Doc
<+> String -> Doc
text String
" ~/.darcs/defaults"

willSendTo :: DryRun -> [String] -> Doc
willSendTo :: DryRun -> [String] -> Doc
willSendTo DryRun
dr [String]
addresses =
    Doc
"Patch bundle" Doc -> Doc -> Doc
<+> Doc
will Doc -> Doc -> Doc
<+> Doc
" be sent to:" Doc -> Doc -> Doc
<+> String -> Doc
text ([String] -> String
unwords [String]
addresses)
  where
    will :: Doc
will = case DryRun
dr of { DryRun
YesDryRun -> Doc
"would"; DryRun
NoDryRun  -> Doc
"will" }

promptTarget :: String
promptTarget :: String
promptTarget = String
"What is the target email address? "

aboutToEdit :: FilePath -> String
aboutToEdit :: String -> String
aboutToEdit String
file = String
"About to edit file " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file

promptNoDescriptionChange :: String
promptNoDescriptionChange :: String
promptNoDescriptionChange = String
"File content did not change. Continue anyway?"