module Darcs.UI.Commands.Log
( changes
, log
, changelog
, logInfoFL
, simpleLogInfo
) where
import Darcs.Prelude
import Data.List ( intersect, find )
import Data.List.Ordered ( nubSort )
import Data.Maybe ( catMaybes, fromMaybe, isJust )
import Control.Arrow ( second )
import Control.Exception ( catch, IOException )
import Control.Monad ( when, unless )
import Control.Monad.State.Strict ( evalState, get, gets, modify )
import Darcs.UI.PrintPatch ( showFriendly )
import Darcs.Patch.PatchInfoAnd ( PatchInfoAndG, fmapFLPIAP, hopefullyM, info )
import Darcs.UI.Commands ( DarcsCommand(..), withStdOpts, nodefaults, commandAlias, findRepository )
import Darcs.UI.Commands.Util ( matchRange )
import Darcs.UI.Completion ( knownFileArgs )
import Darcs.UI.External ( viewDocWith )
import Darcs.UI.Flags
( DarcsFlag
, changesReverse, onlyToFiles, diffingOpts
, useCache, maxCount, hasXmlOutput
, verbosity, isInteractive, verbose
, getRepourl, pathSetFromArgs )
import Darcs.UI.Options ( (^), parseFlags, (?) )
import qualified Darcs.UI.Options.All as O
import Darcs.Util.Path
( SubPath
, AbsolutePath
, simpleSubPath
, AnchoredPath
, floatSubPath
, displayPath
)
import Darcs.Repository ( PatchInfoAnd,
withRepositoryLocation, RepoJob(..),
readPatches, unrecordedChanges,
withRepoLockCanFail )
import Darcs.Util.Lock ( withTempDir )
import Darcs.Patch.Set ( PatchSet, patchSet2RL, Origin )
import Darcs.Patch.Format ( PatchListFormat )
import Darcs.Patch.Info ( toXml, toXmlShort, showPatchInfo, displayPatchInfo, escapeXML, PatchInfo )
import Darcs.Patch.Ident ( PatchId )
import Darcs.Patch.Invertible ( mkInvertible )
import Darcs.Patch.Depends ( contextPatches )
import Darcs.Patch.Show ( ShowPatch, ShowPatchFor(..) )
import Darcs.Patch.TouchesFiles ( lookTouch )
import Darcs.Patch.Apply ( ApplyState )
import Darcs.Patch ( PrimPatchBase(..), invert, xmlSummary, description,
effectOnPaths, listTouchedFiles, showPatch )
import Darcs.Patch.Named ( HasDeps, getdeps )
import Darcs.Patch.Prim.Class ( PrimDetails )
import Darcs.Patch.Summary ( Summary )
import Darcs.Patch.Witnesses.Eq ( EqCheck(..) )
import Darcs.Patch.Witnesses.Ordered
( FL(NilFL), RL(..), filterOutFLFL, filterRL,
reverseFL, (:>)(..), mapFL, mapRL )
import Darcs.Patch.Witnesses.Sealed ( Sealed2(..), unseal2, Sealed(..) )
import Darcs.Patch.Witnesses.Unsafe ( unsafeCoerceP )
import Darcs.Patch.Match
( MatchFlag
, Matchable
, MatchableRP
, matchAPatch
, haveNonrangeMatch
)
import Darcs.Util.Printer
( Doc
, ($$)
, (<+>)
, formatWords
, hsep
, insertBeforeLastline
, prefix
, simplePrinters
, text
, vcat
, vsep
)
import Darcs.Util.Printer.Color ( fancyPrinters )
import Darcs.Util.Progress ( setProgressMode, debugMessage )
import Darcs.UI.SelectChanges ( viewChanges )
import qualified Darcs.UI.SelectChanges as S ( PatchSelectionOptions (..) )
import Darcs.Repository.PatchIndex ( PatchFilter, maybeFilterPatches, attemptCreatePatchIndex )
import Darcs.Util.Tree( Tree )
logHelp :: Doc
logHelp :: Doc
logHelp = [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
"The `darcs log` command lists patches of the current repository or,"
, String
"with `--repo`, a remote repository. Without options or arguments,"
, String
"ALL patches will be listed."
]
, [ String
"When given files or directories paths as arguments, only patches which"
, String
"affect those paths are listed. This includes patches that happened to"
, String
"files before they were moved or renamed."
]
, [ String
"When given `--from-tag` or `--from-patch`, only patches since that tag"
, String
"or patch are listed. Similarly, the `--to-tag` and `--to-patch`"
, String
"options restrict the list to older patches."
]
, [ String
"The `--last` and `--max-count` options both limit the number of patches"
, String
"listed. The former applies BEFORE other filters, whereas the latter"
, String
"applies AFTER other filters. For example `darcs log foo.c"
, String
"--max-count 3` will print the last three patches that affect foo.c,"
, String
"whereas `darcs log --last 3 foo.c` will, of the last three"
, String
"patches, print only those that affect foo.c."
]
, [ String
"Four output formats exist. The default is `--human-readable`. The slightly"
, String
"different `--machine-readable` format enables to see patch dependencies in"
, String
"non-interactive mode. You can also select `--context`, which is an internal"
, String
"format that can be re-read by Darcs (e.g. `darcs clone --context`)."
]
, [ String
"Finally, there is `--xml-output`, which emits valid XML... unless a the"
, String
"patch metadata (author, name or description) contains a non-ASCII"
, String
"character and was recorded in a non-UTF8 locale."
]
]
log :: DarcsCommand
log :: DarcsCommand
log = DarcsCommand
{ commandProgramName :: String
commandProgramName = String
"darcs"
, commandName :: String
commandName = String
"log"
, commandHelp :: Doc
commandHelp = Doc
logHelp
, commandDescription :: String
commandDescription = String
"List patches in the repository."
, commandExtraArgs :: Int
commandExtraArgs = -Int
1
, commandExtraArgHelp :: [String]
commandExtraArgHelp = [String
"[FILE or DIRECTORY]..."]
, commandCompleteArgs :: (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
commandCompleteArgs = (AbsolutePath, AbsolutePath)
-> [DarcsFlag] -> [String] -> IO [String]
knownFileArgs
, commandCommand :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
commandCommand = (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
logCmd
, commandPrereq :: [DarcsFlag] -> IO (Either String ())
commandPrereq = [DarcsFlag] -> IO (Either String ())
findRepository
, commandArgdefaults :: [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
commandArgdefaults = [DarcsFlag] -> AbsolutePath -> [String] -> IO [String]
nodefaults
, commandOptions :: CommandOptions
commandOptions = CommandOptions
logOpts
}
where
logBasicOpts :: OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
logBasicOpts
= PrimOptSpec
DarcsOptDescr
DarcsFlag
(Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
[MatchFlag]
MatchOption
O.matchSeveralOrRange
PrimOptSpec
DarcsOptDescr
DarcsFlag
(Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
[MatchFlag]
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
(Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
(Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
PrimDarcsOption (Maybe Int)
O.maxCount
OptSpec
DarcsOptDescr
DarcsFlag
(Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
(Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
(Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
PrimDarcsOption Bool
O.onlyToFiles
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
(Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 String -> Maybe String -> Maybe Bool -> a)
(Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
PrimDarcsOption (Maybe ChangesFormat)
O.changesFormat
OptSpec
DarcsOptDescr
DarcsFlag
(WithSummary
-> Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
(WithSummary
-> Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 String -> Maybe Bool -> a)
(WithSummary
-> Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption WithSummary
O.withSummary
OptSpec
DarcsOptDescr
DarcsFlag
(Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe String -> Maybe Bool -> a)
(Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 -> Maybe Bool -> a)
(Bool -> Maybe String -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption Bool
O.changesReverse
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe Bool -> a)
(Maybe String -> Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 Bool -> a)
(Maybe String -> Maybe String -> Maybe Bool -> a)
PrimDarcsOption (Maybe String)
O.possiblyRemoteRepo
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe String -> Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool -> a)
(Maybe String -> Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 -> a)
(Maybe String -> Maybe Bool -> a)
PrimDarcsOption (Maybe String)
O.repoDir
OptSpec
DarcsOptDescr
DarcsFlag
(Maybe Bool -> a)
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
-> OptSpec DarcsOptDescr DarcsFlag a (Maybe Bool -> a)
-> OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe 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 (Maybe Bool -> a)
PrimDarcsOption (Maybe Bool)
O.interactive
logAdvancedOpts :: OptSpec
DarcsOptDescr DarcsFlag a (RemoteDarcs -> WithPatchIndex -> a)
logAdvancedOpts = PrimOptSpec
DarcsOptDescr DarcsFlag (WithPatchIndex -> a) RemoteDarcs
PrimDarcsOption RemoteDarcs
O.remoteDarcs PrimOptSpec
DarcsOptDescr DarcsFlag (WithPatchIndex -> a) RemoteDarcs
-> OptSpec DarcsOptDescr DarcsFlag a (WithPatchIndex -> a)
-> OptSpec
DarcsOptDescr DarcsFlag a (RemoteDarcs -> WithPatchIndex -> 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 (WithPatchIndex -> a)
PrimDarcsOption WithPatchIndex
O.patchIndexYes
logOpts :: CommandOptions
logOpts = OptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> RemoteDarcs
-> WithPatchIndex
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> RemoteDarcs
-> WithPatchIndex
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
forall {a}.
OptSpec
DarcsOptDescr
DarcsFlag
a
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> a)
logBasicOpts OptSpec
DarcsOptDescr
DarcsFlag
(Maybe StdCmdAction
-> Verbosity
-> RemoteDarcs
-> WithPatchIndex
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
([MatchFlag]
-> Maybe Int
-> Bool
-> Maybe ChangesFormat
-> WithSummary
-> Bool
-> Maybe String
-> Maybe String
-> Maybe Bool
-> Maybe StdCmdAction
-> Verbosity
-> RemoteDarcs
-> WithPatchIndex
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(RemoteDarcs
-> WithPatchIndex
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
-> CommandOptions
forall b c.
DarcsOption (Maybe StdCmdAction -> Verbosity -> b) c
-> DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
b
-> CommandOptions
`withStdOpts` DarcsOption
(UseCache
-> UseIndex -> HooksConfig -> Bool -> Bool -> [DarcsFlag])
(RemoteDarcs
-> WithPatchIndex
-> UseCache
-> UseIndex
-> HooksConfig
-> Bool
-> Bool
-> [DarcsFlag])
forall {a}.
OptSpec
DarcsOptDescr DarcsFlag a (RemoteDarcs -> WithPatchIndex -> a)
logAdvancedOpts
logCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
logCmd :: (AbsolutePath, AbsolutePath) -> [DarcsFlag] -> [String] -> IO ()
logCmd (AbsolutePath, AbsolutePath)
fps [DarcsFlag]
opts [String]
args
| PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe ChangesFormat)
PrimDarcsOption (Maybe ChangesFormat)
O.changesFormat PrimDarcsOption (Maybe ChangesFormat)
-> [DarcsFlag] -> Maybe ChangesFormat
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts Maybe ChangesFormat -> Maybe ChangesFormat -> Bool
forall a. Eq a => a -> a -> Bool
== ChangesFormat -> Maybe ChangesFormat
forall a. a -> Maybe a
Just ChangesFormat
O.GenContext = if Bool -> Bool
not (Bool -> Bool) -> ([String] -> Bool) -> [String] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([String] -> Bool) -> [String] -> Bool
forall a b. (a -> b) -> a -> b
$ [String]
args
then String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"log --context cannot accept other arguments"
else [DarcsFlag] -> IO ()
logContext [DarcsFlag]
opts
| [DarcsFlag] -> Bool
hasRemoteRepo [DarcsFlag]
opts = do
([SubPath]
fs, [String]
es) <- [String] -> [String] -> IO ([SubPath], [String])
remoteSubPaths [String]
args []
if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
es then
String -> (AbsolutePath -> IO ()) -> IO ()
forall a. String -> (AbsolutePath -> IO a) -> IO a
withTempDir String
"darcs.log"
(\AbsolutePath
_ -> [DarcsFlag] -> Maybe [AnchoredPath] -> IO ()
showLog [DarcsFlag]
opts (Maybe [AnchoredPath] -> IO ()) -> Maybe [AnchoredPath] -> IO ()
forall a b. (a -> b) -> a -> b
$ [AnchoredPath] -> Maybe [AnchoredPath]
forall a. [a] -> Maybe [a]
maybeNotNull ([AnchoredPath] -> Maybe [AnchoredPath])
-> [AnchoredPath] -> Maybe [AnchoredPath]
forall a b. (a -> b) -> a -> b
$ [AnchoredPath] -> [AnchoredPath]
forall a. Ord a => [a] -> [a]
nubSort ([AnchoredPath] -> [AnchoredPath])
-> [AnchoredPath] -> [AnchoredPath]
forall a b. (a -> b) -> a -> b
$ [Either String AnchoredPath] -> [AnchoredPath]
forall e a. [Either e a] -> [a]
filterErrors ([Either String AnchoredPath] -> [AnchoredPath])
-> [Either String AnchoredPath] -> [AnchoredPath]
forall a b. (a -> b) -> a -> b
$ (SubPath -> Either String AnchoredPath)
-> [SubPath] -> [Either String AnchoredPath]
forall a b. (a -> b) -> [a] -> [b]
map SubPath -> Either String AnchoredPath
floatSubPath [SubPath]
fs)
else
String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"For a remote repo I can only handle relative paths.\n"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"Invalid arguments: "String -> String -> String
forall a. [a] -> [a] -> [a]
++[String] -> String
unwords [String]
es
| [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
args = [DarcsFlag] -> Maybe [AnchoredPath] -> IO ()
showLog [DarcsFlag]
opts Maybe [AnchoredPath]
forall a. Maybe a
Nothing
| Bool
otherwise = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Bool -> [DarcsFlag] -> Bool
isInteractive Bool
False [DarcsFlag]
opts)
(IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (PrimOptSpec DarcsOptDescr DarcsFlag a WithPatchIndex
PrimDarcsOption WithPatchIndex
O.patchIndexNo PrimDarcsOption WithPatchIndex -> [DarcsFlag] -> WithPatchIndex
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts WithPatchIndex -> WithPatchIndex -> Bool
forall a. Eq a => a -> a -> Bool
== WithPatchIndex
O.YesPatchIndex)
(IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ UseCache -> RepoJob 'RO () -> IO ()
withRepoLockCanFail (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
(RepoJob 'RO () -> IO ()) -> RepoJob 'RO () -> IO ()
forall a b. (a -> b) -> a -> b
$ TreePatchJob 'RO () -> RepoJob 'RO ()
forall (rt :: AccessType) a. TreePatchJob rt a -> RepoJob rt a
RepoJob (\Repository 'RO p wU wR
repo -> Repository 'RO p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p wU wR
repo IO (PatchSet p Origin wR)
-> (PatchSet p Origin wR -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Repository 'RO p wU wR -> PatchSet p Origin wR -> IO ()
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wU wR -> PatchSet p Origin wR -> IO ()
attemptCreatePatchIndex Repository 'RO p wU wR
repo)
Maybe [AnchoredPath]
paths <- (AbsolutePath, AbsolutePath)
-> [String] -> IO (Maybe [AnchoredPath])
pathSetFromArgs (AbsolutePath, AbsolutePath)
fps [String]
args
[DarcsFlag] -> Maybe [AnchoredPath] -> IO ()
showLog [DarcsFlag]
opts Maybe [AnchoredPath]
paths
maybeNotNull :: [a] -> Maybe [a]
maybeNotNull :: forall a. [a] -> Maybe [a]
maybeNotNull [] = Maybe [a]
forall a. Maybe a
Nothing
maybeNotNull [a]
xs = [a] -> Maybe [a]
forall a. a -> Maybe a
Just [a]
xs
filterErrors :: [Either e a] -> [a]
filterErrors :: forall e a. [Either e a] -> [a]
filterErrors = [Maybe a] -> [a]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe a] -> [a])
-> ([Either e a] -> [Maybe a]) -> [Either e a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either e a -> Maybe a) -> [Either e a] -> [Maybe a]
forall a b. (a -> b) -> [a] -> [b]
map ((e -> Maybe a) -> (a -> Maybe a) -> Either e a -> Maybe a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe a -> e -> Maybe a
forall a b. a -> b -> a
const Maybe a
forall a. Maybe a
Nothing) a -> Maybe a
forall a. a -> Maybe a
Just)
hasRemoteRepo :: [DarcsFlag] -> Bool
hasRemoteRepo :: [DarcsFlag] -> Bool
hasRemoteRepo = Maybe String -> Bool
forall a. Maybe a -> Bool
isJust (Maybe String -> Bool)
-> ([DarcsFlag] -> Maybe String) -> [DarcsFlag] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [DarcsFlag] -> Maybe String
getRepourl
remoteSubPaths :: [String] -> [String] -> IO ([SubPath],[String])
remoteSubPaths :: [String] -> [String] -> IO ([SubPath], [String])
remoteSubPaths [] [String]
es = ([SubPath], [String]) -> IO ([SubPath], [String])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([], [String]
es)
remoteSubPaths (String
arg:[String]
args) [String]
es = case HasCallStack => String -> Maybe SubPath
String -> Maybe SubPath
simpleSubPath String
arg of
Maybe SubPath
Nothing -> [String] -> [String] -> IO ([SubPath], [String])
remoteSubPaths [String]
args (String
argString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
es)
Just SubPath
sp -> do
([SubPath]
sps, [String]
es') <- [String] -> [String] -> IO ([SubPath], [String])
remoteSubPaths [String]
args [String]
es
([SubPath], [String]) -> IO ([SubPath], [String])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SubPath
spSubPath -> [SubPath] -> [SubPath]
forall a. a -> [a] -> [a]
:[SubPath]
sps, [String]
es')
showLog :: [DarcsFlag] -> Maybe [AnchoredPath] -> IO ()
showLog :: [DarcsFlag] -> Maybe [AnchoredPath] -> IO ()
showLog [DarcsFlag]
opts Maybe [AnchoredPath]
files =
let repodir :: String
repodir = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"." ([DarcsFlag] -> Maybe String
getRepourl [DarcsFlag]
opts) in
UseCache -> String -> RepoJob 'RO () -> IO ()
forall a. UseCache -> String -> RepoJob 'RO a -> IO a
withRepositoryLocation (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) String
repodir (RepoJob 'RO () -> IO ()) -> RepoJob 'RO () -> IO ()
forall a b. (a -> b) -> a -> b
$ TreePatchJob 'RO () -> RepoJob 'RO ()
forall (rt :: AccessType) a. TreePatchJob rt a -> RepoJob rt a
RepoJob (TreePatchJob 'RO () -> RepoJob 'RO ())
-> TreePatchJob 'RO () -> RepoJob 'RO ()
forall a b. (a -> b) -> a -> b
$ \Repository 'RO p wU wR
repository -> do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
O.debug 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
$ Bool -> IO ()
setProgressMode Bool
False
Sealed FL (PrimOf p) wR wX
unrec <- case Maybe [AnchoredPath]
files of
Maybe [AnchoredPath]
Nothing -> Sealed (FL (PrimOf p) wR) -> IO (Sealed (FL (PrimOf p) wR))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Sealed (FL (PrimOf p) wR) -> IO (Sealed (FL (PrimOf p) wR)))
-> Sealed (FL (PrimOf p) wR) -> IO (Sealed (FL (PrimOf p) wR))
forall a b. (a -> b) -> a -> b
$ FL (PrimOf p) wR wR -> Sealed (FL (PrimOf p) wR)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed FL (PrimOf p) wR wR
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL
Just [AnchoredPath]
_ ->
FL (PrimOf p) wR wU -> Sealed (FL (PrimOf p) wR)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed (FL (PrimOf p) wR wU -> Sealed (FL (PrimOf p) wR))
-> IO (FL (PrimOf p) wR wU) -> IO (Sealed (FL (PrimOf p) wR))
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` DiffOpts
-> Repository 'RO p wU wR
-> Maybe [AnchoredPath]
-> IO (FL (PrimOf p) wR wU)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
DiffOpts
-> Repository rt p wU wR
-> Maybe [AnchoredPath]
-> IO (FL (PrimOf p) wR wU)
unrecordedChanges ([DarcsFlag] -> DiffOpts
diffingOpts [DarcsFlag]
opts) Repository 'RO p wU wR
repository Maybe [AnchoredPath]
files IO (Sealed (FL (PrimOf p) wR))
-> (IOException -> IO (Sealed (FL (PrimOf p) wR)))
-> IO (Sealed (FL (PrimOf p) wR))
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch`
\(IOException
_ :: IOException) ->
Sealed (FL (PrimOf p) wR) -> IO (Sealed (FL (PrimOf p) wR))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FL (PrimOf p) wR wR -> Sealed (FL (PrimOf p) wR)
forall (a :: * -> *) wX. a wX -> Sealed a
Sealed FL (PrimOf p) wR wR
forall (a :: * -> * -> *) wX. FL a wX wX
NilFL)
String -> IO ()
debugMessage String
"About to read the repository..."
PatchSet p Origin wR
patches <- Repository 'RO p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p wU wR
repository
String -> IO ()
debugMessage String
"Done reading the repository."
let recFiles :: Maybe [AnchoredPath]
recFiles = FL (PrimOf p) wX wR -> [AnchoredPath] -> [AnchoredPath]
forall (p :: * -> * -> *) wX wY.
(Apply p, ApplyState p ~ Tree) =>
p wX wY -> [AnchoredPath] -> [AnchoredPath]
effectOnPaths (FL (PrimOf p) wR wX -> FL (PrimOf p) wX wR
forall wX wY. FL (PrimOf p) wX wY -> FL (PrimOf p) wY wX
forall (p :: * -> * -> *) wX wY. Invert p => p wX wY -> p wY wX
invert FL (PrimOf p) wR wX
unrec) ([AnchoredPath] -> [AnchoredPath])
-> Maybe [AnchoredPath] -> Maybe [AnchoredPath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [AnchoredPath]
files
filtered_changes :: PatchSet p Origin wY -> IO (LogInfo (PatchInfoAnd p))
filtered_changes PatchSet p Origin wY
p =
LogInfo (PatchInfoAnd p) -> LogInfo (PatchInfoAnd p)
forall {p :: * -> * -> *}. LogInfo p -> LogInfo p
maybe_reverse (LogInfo (PatchInfoAnd p) -> LogInfo (PatchInfoAnd p))
-> IO (LogInfo (PatchInfoAnd p)) -> IO (LogInfo (PatchInfoAnd p))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Maybe Int
-> [MatchFlag]
-> Bool
-> Maybe [AnchoredPath]
-> PatchFilter p
-> PatchSet p Origin wY
-> IO (LogInfo (PatchInfoAnd p))
forall (p :: * -> * -> *) wY.
(MatchableRP p, ApplyState p ~ Tree) =>
Maybe Int
-> [MatchFlag]
-> Bool
-> Maybe [AnchoredPath]
-> PatchFilter p
-> PatchSet p Origin wY
-> IO (LogInfo (PatchInfoAnd p))
getLogInfo
(PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe Int)
PrimDarcsOption (Maybe Int)
maxCount PrimDarcsOption (Maybe Int) -> [DarcsFlag] -> Maybe Int
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
(MatchOption -> [DarcsFlag] -> [MatchFlag]
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimOptSpec DarcsOptDescr DarcsFlag a [MatchFlag]
MatchOption
O.matchSeveralOrRange [DarcsFlag]
opts)
(PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
onlyToFiles PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts)
Maybe [AnchoredPath]
recFiles
(Repository 'RO p wU wR -> PatchSet p Origin wR -> PatchFilter p
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
(RepoPatch p, ApplyState p ~ Tree) =>
Repository rt p wU wR -> PatchSet p Origin wR -> PatchFilter p
maybeFilterPatches Repository 'RO p wU wR
repository PatchSet p Origin wR
patches)
PatchSet p Origin wY
p
if Bool -> [DarcsFlag] -> Bool
isInteractive Bool
False [DarcsFlag]
opts
then do LogInfo (PatchInfoAnd p)
li <- PatchSet p Origin wR -> IO (LogInfo (PatchInfoAnd p))
forall {wY}. PatchSet p Origin wY -> IO (LogInfo (PatchInfoAnd p))
filtered_changes PatchSet p Origin wR
patches
PatchSelectionOptions -> [Sealed2 (PatchInfoAnd p)] -> IO ()
forall (p :: * -> * -> *).
(ShowPatch p, ShowContextPatch p, ApplyState p ~ Tree) =>
PatchSelectionOptions -> [Sealed2 p] -> IO ()
viewChanges ([DarcsFlag] -> PatchSelectionOptions
logPatchSelOpts [DarcsFlag]
opts) (((Sealed2 (PatchInfoAnd p), [AnchoredPath])
-> Sealed2 (PatchInfoAnd p))
-> [(Sealed2 (PatchInfoAnd p), [AnchoredPath])]
-> [Sealed2 (PatchInfoAnd p)]
forall a b. (a -> b) -> [a] -> [b]
map (Sealed2 (PatchInfoAnd p), [AnchoredPath])
-> Sealed2 (PatchInfoAnd p)
forall a b. (a, b) -> a
fst (LogInfo (PatchInfoAnd p)
-> [(Sealed2 (PatchInfoAnd p), [AnchoredPath])]
forall (p :: * -> * -> *).
LogInfo p -> [(Sealed2 p, [AnchoredPath])]
liPatches LogInfo (PatchInfoAnd p)
li))
else do let header :: Doc
header =
case Maybe [AnchoredPath]
recFiles of
Just [AnchoredPath]
fs | Bool -> Bool
not ([DarcsFlag] -> Bool
hasXmlOutput [DarcsFlag]
opts) ->
let pathlist :: [Doc]
pathlist = (AnchoredPath -> Doc) -> [AnchoredPath] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Doc
text (String -> Doc) -> (AnchoredPath -> String) -> AnchoredPath -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredPath -> String
displayPath) [AnchoredPath]
fs
in [Doc] -> Doc
hsep (String -> Doc
text String
"Changes to" Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [Doc]
pathlist) Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text String
":" Doc -> Doc -> Doc
$$ String -> Doc
text String
""
Maybe [AnchoredPath]
_ -> Doc
forall a. Monoid a => a
mempty
String -> IO ()
debugMessage String
"About to print the patches..."
let printers :: Printers
printers = if [DarcsFlag] -> Bool
hasXmlOutput [DarcsFlag]
opts then Printers
simplePrinters else Printers
fancyPrinters
PatchSet p Origin wR
ps <- Repository 'RO p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p wU wR
repository
Doc
logOutput <- [DarcsFlag]
-> RL (PatchInfoAnd p) Origin wR -> LogInfo (PatchInfoAnd p) -> Doc
forall (p :: * -> * -> *) wStart wX.
(ShowPatch p, PatchListFormat p, Summary p, HasDeps p,
PrimDetails (PrimOf p)) =>
[DarcsFlag]
-> RL (PatchInfoAndG p) wStart wX
-> LogInfo (PatchInfoAndG p)
-> Doc
changelog [DarcsFlag]
opts (PatchSet p Origin wR -> RL (PatchInfoAnd p) Origin wR
forall (p :: * -> * -> *) wStart wX.
PatchSet p wStart wX -> RL (PatchInfoAnd p) wStart wX
patchSet2RL PatchSet p Origin wR
ps) (LogInfo (PatchInfoAnd p) -> Doc)
-> IO (LogInfo (PatchInfoAnd p)) -> IO Doc
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` PatchSet p Origin wR -> IO (LogInfo (PatchInfoAnd p))
forall {wY}. PatchSet p Origin wY -> IO (LogInfo (PatchInfoAnd p))
filtered_changes PatchSet p Origin wR
patches
Printers -> Doc -> IO ()
viewDocWith Printers
printers (Doc
header Doc -> Doc -> Doc
$$ Doc
logOutput)
where
maybe_reverse :: LogInfo p -> LogInfo p
maybe_reverse li :: LogInfo p
li@(LogInfo [(Sealed2 p, [AnchoredPath])]
xs [(AnchoredPath, AnchoredPath)]
b Maybe Doc
c) =
if PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
changesReverse PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts then [(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
forall (p :: * -> * -> *).
[(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
LogInfo ([(Sealed2 p, [AnchoredPath])] -> [(Sealed2 p, [AnchoredPath])]
forall a. [a] -> [a]
reverse [(Sealed2 p, [AnchoredPath])]
xs) [(AnchoredPath, AnchoredPath)]
b Maybe Doc
c else LogInfo p
li
data LogInfo p = LogInfo
{ forall (p :: * -> * -> *).
LogInfo p -> [(Sealed2 p, [AnchoredPath])]
liPatches :: [(Sealed2 p, [AnchoredPath])]
, forall (p :: * -> * -> *).
LogInfo p -> [(AnchoredPath, AnchoredPath)]
liRenames :: [(AnchoredPath, AnchoredPath)]
, forall (p :: * -> * -> *). LogInfo p -> Maybe Doc
liErrorMsg :: Maybe Doc
}
mkLogInfo :: [Sealed2 p] -> LogInfo p
mkLogInfo :: forall (p :: * -> * -> *). [Sealed2 p] -> LogInfo p
mkLogInfo [Sealed2 p]
ps = [(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
forall (p :: * -> * -> *).
[(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
LogInfo ((Sealed2 p -> (Sealed2 p, [AnchoredPath]))
-> [Sealed2 p] -> [(Sealed2 p, [AnchoredPath])]
forall a b. (a -> b) -> [a] -> [b]
map (,[]) [Sealed2 p]
ps) [] Maybe Doc
forall a. Maybe a
Nothing
logInfoFL :: FL p wX wY -> LogInfo p
logInfoFL :: forall (p :: * -> * -> *) wX wY. FL p wX wY -> LogInfo p
logInfoFL = [Sealed2 p] -> LogInfo p
forall (p :: * -> * -> *). [Sealed2 p] -> LogInfo p
mkLogInfo ([Sealed2 p] -> LogInfo p)
-> (FL p wX wY -> [Sealed2 p]) -> FL p wX wY -> LogInfo p
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall wW wZ. p wW wZ -> Sealed2 p) -> FL p wX wY -> [Sealed2 p]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL p wW wZ -> Sealed2 p
forall wW wZ. p wW wZ -> Sealed2 p
forall (a :: * -> * -> *) wX wY. a wX wY -> Sealed2 a
Sealed2
matchNonrange :: (Matchable p, PatchId p ~ PatchInfo)
=> [MatchFlag] -> RL p wA wB -> [Sealed2 p]
matchNonrange :: forall (p :: * -> * -> *) wA wB.
(Matchable p, PatchId p ~ PatchInfo) =>
[MatchFlag] -> RL p wA wB -> [Sealed2 p]
matchNonrange [MatchFlag]
matchFlags
| [MatchFlag] -> Bool
haveNonrangeMatch [MatchFlag]
matchFlags = (forall wX wY. p wX wY -> Bool) -> RL p wA wB -> [Sealed2 p]
forall (p :: * -> * -> *) wA wB.
(forall wX wY. p wX wY -> Bool) -> RL p wA wB -> [Sealed2 p]
filterRL ([MatchFlag] -> p wX wY -> Bool
forall (p :: * -> * -> *) wX wY.
Matchable p =>
[MatchFlag] -> p wX wY -> Bool
matchAPatch [MatchFlag]
matchFlags)
| Bool
otherwise = (forall wW wZ. p wW wZ -> Sealed2 p) -> RL p wA wB -> [Sealed2 p]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> RL a wX wY -> [b]
mapRL p wW wZ -> Sealed2 p
forall wW wZ. p wW wZ -> Sealed2 p
forall (a :: * -> * -> *) wX wY. a wX wY -> Sealed2 a
Sealed2
simpleLogInfo :: ( MatchableRP p
, ApplyState p ~ Tree
)
=> AnchoredPath
-> PatchFilter p
-> PatchSet p Origin wY
-> IO [Sealed2 (PatchInfoAnd p)]
simpleLogInfo :: forall (p :: * -> * -> *) wY.
(MatchableRP p, ApplyState p ~ Tree) =>
AnchoredPath
-> PatchFilter p
-> PatchSet p Origin wY
-> IO [Sealed2 (PatchInfoAnd p)]
simpleLogInfo AnchoredPath
path PatchFilter p
pf PatchSet p Origin wY
ps =
((Sealed2 (PatchInfoAnd p), [AnchoredPath])
-> Sealed2 (PatchInfoAnd p))
-> [(Sealed2 (PatchInfoAnd p), [AnchoredPath])]
-> [Sealed2 (PatchInfoAnd p)]
forall a b. (a -> b) -> [a] -> [b]
map (Sealed2 (PatchInfoAnd p), [AnchoredPath])
-> Sealed2 (PatchInfoAnd p)
forall a b. (a, b) -> a
fst ([(Sealed2 (PatchInfoAnd p), [AnchoredPath])]
-> [Sealed2 (PatchInfoAnd p)])
-> (LogInfo (PatchInfoAnd p)
-> [(Sealed2 (PatchInfoAnd p), [AnchoredPath])])
-> LogInfo (PatchInfoAnd p)
-> [Sealed2 (PatchInfoAnd p)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogInfo (PatchInfoAnd p)
-> [(Sealed2 (PatchInfoAnd p), [AnchoredPath])]
forall (p :: * -> * -> *).
LogInfo p -> [(Sealed2 p, [AnchoredPath])]
liPatches (LogInfo (PatchInfoAnd p) -> [Sealed2 (PatchInfoAnd p)])
-> IO (LogInfo (PatchInfoAnd p)) -> IO [Sealed2 (PatchInfoAnd p)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
-> [MatchFlag]
-> Bool
-> Maybe [AnchoredPath]
-> PatchFilter p
-> PatchSet p Origin wY
-> IO (LogInfo (PatchInfoAnd p))
forall (p :: * -> * -> *) wY.
(MatchableRP p, ApplyState p ~ Tree) =>
Maybe Int
-> [MatchFlag]
-> Bool
-> Maybe [AnchoredPath]
-> PatchFilter p
-> PatchSet p Origin wY
-> IO (LogInfo (PatchInfoAnd p))
getLogInfo Maybe Int
forall a. Maybe a
Nothing [] Bool
False ([AnchoredPath] -> Maybe [AnchoredPath]
forall a. a -> Maybe a
Just [AnchoredPath
path]) PatchFilter p
pf PatchSet p Origin wY
ps
getLogInfo :: forall p wY.
( MatchableRP p
, ApplyState p ~ Tree
)
=> Maybe Int -> [MatchFlag] -> Bool
-> Maybe [AnchoredPath]
-> PatchFilter p
-> PatchSet p Origin wY
-> IO (LogInfo (PatchInfoAnd p))
getLogInfo :: forall (p :: * -> * -> *) wY.
(MatchableRP p, ApplyState p ~ Tree) =>
Maybe Int
-> [MatchFlag]
-> Bool
-> Maybe [AnchoredPath]
-> PatchFilter p
-> PatchSet p Origin wY
-> IO (LogInfo (PatchInfoAnd p))
getLogInfo Maybe Int
maxCountFlag [MatchFlag]
matchFlags Bool
onlyToFilesFlag Maybe [AnchoredPath]
paths PatchFilter p
patchFilter PatchSet p Origin wY
ps =
case [MatchFlag]
-> PatchSet p Origin wY -> Sealed2 (FL (PatchInfoAnd p))
forall (p :: * -> * -> *) wY.
MatchableRP p =>
[MatchFlag]
-> PatchSet p Origin wY -> Sealed2 (FL (PatchInfoAnd p))
matchRange [MatchFlag]
matchFlags PatchSet p Origin wY
ps of
Sealed2 FL (PatchInfoAnd p) wX wY
range ->
let ps' :: [Sealed2 (PatchInfoAnd p)]
ps' = [MatchFlag]
-> RL (PatchInfoAnd p) wX wY -> [Sealed2 (PatchInfoAnd p)]
forall (p :: * -> * -> *) wA wB.
(Matchable p, PatchId p ~ PatchInfo) =>
[MatchFlag] -> RL p wA wB -> [Sealed2 p]
matchNonrange [MatchFlag]
matchFlags (FL (PatchInfoAnd p) wX wY -> RL (PatchInfoAnd p) wX wY
forall (a :: * -> * -> *) wX wZ. FL a wX wZ -> RL a wX wZ
reverseFL FL (PatchInfoAnd p) wX wY
range) in
case Maybe [AnchoredPath]
paths of
Maybe [AnchoredPath]
Nothing -> LogInfo (PatchInfoAnd p) -> IO (LogInfo (PatchInfoAnd p))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LogInfo (PatchInfoAnd p) -> IO (LogInfo (PatchInfoAnd p)))
-> LogInfo (PatchInfoAnd p) -> IO (LogInfo (PatchInfoAnd p))
forall a b. (a -> b) -> a -> b
$ [Sealed2 (PatchInfoAnd p)] -> LogInfo (PatchInfoAnd p)
forall (p :: * -> * -> *). [Sealed2 p] -> LogInfo p
mkLogInfo ([Sealed2 (PatchInfoAnd p)] -> LogInfo (PatchInfoAnd p))
-> [Sealed2 (PatchInfoAnd p)] -> LogInfo (PatchInfoAnd p)
forall a b. (a -> b) -> a -> b
$ ([Sealed2 (PatchInfoAnd p)] -> [Sealed2 (PatchInfoAnd p)])
-> (Int
-> [Sealed2 (PatchInfoAnd p)] -> [Sealed2 (PatchInfoAnd p)])
-> Maybe Int
-> [Sealed2 (PatchInfoAnd p)]
-> [Sealed2 (PatchInfoAnd p)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Sealed2 (PatchInfoAnd p)] -> [Sealed2 (PatchInfoAnd p)]
forall a. a -> a
id Int -> [Sealed2 (PatchInfoAnd p)] -> [Sealed2 (PatchInfoAnd p)]
forall a. Int -> [a] -> [a]
take Maybe Int
maxCountFlag [Sealed2 (PatchInfoAnd p)]
ps'
Just [AnchoredPath]
fs -> do
LogInfo (PatchInfoAnd p) -> LogInfo (PatchInfoAnd p)
forall {q :: * -> * -> *}.
PatchInspect q =>
LogInfo (PatchInfoAndG (Named q))
-> LogInfo (PatchInfoAndG (Named q))
filterOutUnrelatedChanges (LogInfo (PatchInfoAnd p) -> LogInfo (PatchInfoAnd p))
-> IO (LogInfo (PatchInfoAnd p)) -> IO (LogInfo (PatchInfoAnd p))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
[Sealed2 (PatchInfoAnd p)]
ps'' <- PatchFilter p
patchFilter [AnchoredPath]
fs [Sealed2 (PatchInfoAnd p)]
ps'
LogInfo (PatchInfoAnd p) -> IO (LogInfo (PatchInfoAnd p))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LogInfo (PatchInfoAnd p) -> IO (LogInfo (PatchInfoAnd p)))
-> LogInfo (PatchInfoAnd p) -> IO (LogInfo (PatchInfoAnd p))
forall a b. (a -> b) -> a -> b
$ Maybe Int
-> [AnchoredPath]
-> [Sealed2 (PatchInfoAnd p)]
-> LogInfo (PatchInfoAnd p)
forall (p :: * -> * -> *).
(MatchableRP p, ApplyState p ~ Tree) =>
Maybe Int
-> [AnchoredPath]
-> [Sealed2 (PatchInfoAnd p)]
-> LogInfo (PatchInfoAnd p)
filterPatchesByNames Maybe Int
maxCountFlag [AnchoredPath]
fs [Sealed2 (PatchInfoAnd p)]
ps''
where
filterOutUnrelatedChanges :: LogInfo (PatchInfoAndG (Named q))
-> LogInfo (PatchInfoAndG (Named q))
filterOutUnrelatedChanges LogInfo (PatchInfoAndG (Named q))
li
| Bool
onlyToFilesFlag = LogInfo (PatchInfoAndG (Named q))
li { liPatches = map onlyRelated (liPatches li) }
| Bool
otherwise = LogInfo (PatchInfoAndG (Named q))
li
onlyRelated :: (Sealed2 (PatchInfoAndG (Named q)), [AnchoredPath])
-> (Sealed2 (PatchInfoAndG (Named q)), [AnchoredPath])
onlyRelated (Sealed2 PatchInfoAndG (Named q) wX wY
p, [AnchoredPath]
fs) =
(PatchInfoAndG (Named q) wX wY -> Sealed2 (PatchInfoAndG (Named q))
forall (a :: * -> * -> *) wX wY. a wX wY -> Sealed2 a
Sealed2 (PatchInfoAndG (Named q) wX wY
-> Sealed2 (PatchInfoAndG (Named q)))
-> PatchInfoAndG (Named q) wX wY
-> Sealed2 (PatchInfoAndG (Named q))
forall a b. (a -> b) -> a -> b
$ (FL q wX wY -> FL q wX wY)
-> PatchInfoAndG (Named q) wX wY -> PatchInfoAndG (Named q) wX wY
forall (p :: * -> * -> *) wX wY (q :: * -> * -> *).
(FL p wX wY -> FL q wX wY)
-> PatchInfoAnd p wX wY -> PatchInfoAnd q wX wY
fmapFLPIAP ((forall wX wY. q wX wY -> EqCheck wX wY)
-> FL q wX wY -> FL q wX wY
forall (p :: * -> * -> *) wW wZ.
(forall wX wY. p wX wY -> EqCheck wX wY)
-> FL p wW wZ -> FL p wW wZ
filterOutFLFL ([AnchoredPath] -> q wX wY -> EqCheck wX wY
forall {p :: * -> * -> *} {wX} {wY} {wB} {wC}.
PatchInspect p =>
[AnchoredPath] -> p wX wY -> EqCheck wB wC
unrelated [AnchoredPath]
fs)) PatchInfoAndG (Named q) wX wY
p, [AnchoredPath]
fs)
unrelated :: [AnchoredPath] -> p wX wY -> EqCheck wB wC
unrelated [AnchoredPath]
fs p wX wY
p
| [AnchoredPath] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([AnchoredPath] -> Bool) -> [AnchoredPath] -> Bool
forall a b. (a -> b) -> a -> b
$ [AnchoredPath]
fs [AnchoredPath] -> [AnchoredPath] -> [AnchoredPath]
forall a. Eq a => [a] -> [a] -> [a]
`intersect` p wX wY -> [AnchoredPath]
forall wX wY. p wX wY -> [AnchoredPath]
forall (p :: * -> * -> *) wX wY.
PatchInspect p =>
p wX wY -> [AnchoredPath]
listTouchedFiles p wX wY
p = EqCheck Any Any -> EqCheck wB wC
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP EqCheck Any Any
forall wA. EqCheck wA wA
IsEq
| Bool
otherwise = EqCheck wB wC
forall wA wB. EqCheck wA wB
NotEq
filterPatchesByNames
:: forall p.
( MatchableRP p
, ApplyState p ~ Tree
)
=> Maybe Int
-> [AnchoredPath]
-> [Sealed2 (PatchInfoAnd p)]
-> LogInfo (PatchInfoAnd p)
filterPatchesByNames :: forall (p :: * -> * -> *).
(MatchableRP p, ApplyState p ~ Tree) =>
Maybe Int
-> [AnchoredPath]
-> [Sealed2 (PatchInfoAnd p)]
-> LogInfo (PatchInfoAnd p)
filterPatchesByNames Maybe Int
maxcount [AnchoredPath]
paths [Sealed2 (PatchInfoAnd p)]
patches = LogInfo (PatchInfoAnd p) -> LogInfo (PatchInfoAnd p)
forall {p :: * -> * -> *}. LogInfo p -> LogInfo p
removeNonRenames (LogInfo (PatchInfoAnd p) -> LogInfo (PatchInfoAnd p))
-> LogInfo (PatchInfoAnd p) -> LogInfo (PatchInfoAnd p)
forall a b. (a -> b) -> a -> b
$
State
(Maybe Int, [(AnchoredPath, AnchoredPath)])
(LogInfo (PatchInfoAnd p))
-> (Maybe Int, [(AnchoredPath, AnchoredPath)])
-> LogInfo (PatchInfoAnd p)
forall s a. State s a -> s -> a
evalState ([AnchoredPath]
-> [Sealed2 (PatchInfoAnd p)]
-> State
(Maybe Int, [(AnchoredPath, AnchoredPath)])
(LogInfo (PatchInfoAnd p))
forall {p :: * -> * -> *}.
(ApplyState p ~ Tree, Apply p) =>
[AnchoredPath]
-> [Sealed2 (PatchInfoAndG p)]
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
filterPatchesByNamesM [AnchoredPath]
paths [Sealed2 (PatchInfoAnd p)]
patches) (Maybe Int
maxcount, [(AnchoredPath, AnchoredPath)]
initRenames) where
removeNonRenames :: LogInfo p -> LogInfo p
removeNonRenames LogInfo p
li = LogInfo p
li { liRenames = removeIds (liRenames li) }
removeIds :: [(AnchoredPath, AnchoredPath)] -> [(AnchoredPath, AnchoredPath)]
removeIds = ((AnchoredPath, AnchoredPath) -> Bool)
-> [(AnchoredPath, AnchoredPath)] -> [(AnchoredPath, AnchoredPath)]
forall a. (a -> Bool) -> [a] -> [a]
filter (((AnchoredPath, AnchoredPath) -> Bool)
-> [(AnchoredPath, AnchoredPath)]
-> [(AnchoredPath, AnchoredPath)])
-> ((AnchoredPath, AnchoredPath) -> Bool)
-> [(AnchoredPath, AnchoredPath)]
-> [(AnchoredPath, AnchoredPath)]
forall a b. (a -> b) -> a -> b
$ (AnchoredPath -> AnchoredPath -> Bool)
-> (AnchoredPath, AnchoredPath) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry AnchoredPath -> AnchoredPath -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
initRenames :: [(AnchoredPath, AnchoredPath)]
initRenames = (AnchoredPath -> (AnchoredPath, AnchoredPath))
-> [AnchoredPath] -> [(AnchoredPath, AnchoredPath)]
forall a b. (a -> b) -> [a] -> [b]
map (\AnchoredPath
x -> (AnchoredPath
x, AnchoredPath
x)) [AnchoredPath]
paths
returnFinal :: StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity (LogInfo p)
returnFinal = (\[(AnchoredPath, AnchoredPath)]
renames -> [(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
forall (p :: * -> * -> *).
[(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
LogInfo [] [(AnchoredPath, AnchoredPath)]
renames Maybe Doc
forall a. Maybe a
Nothing) ([(AnchoredPath, AnchoredPath)] -> LogInfo p)
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
[(AnchoredPath, AnchoredPath)]
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity (LogInfo p)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Maybe Int, [(AnchoredPath, AnchoredPath)])
-> [(AnchoredPath, AnchoredPath)])
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
[(AnchoredPath, AnchoredPath)]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (Maybe Int, [(AnchoredPath, AnchoredPath)])
-> [(AnchoredPath, AnchoredPath)]
forall a b. (a, b) -> b
snd
filterPatchesByNamesM :: [AnchoredPath]
-> [Sealed2 (PatchInfoAndG p)]
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
filterPatchesByNamesM [] [Sealed2 (PatchInfoAndG p)]
_ = StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
forall {p :: * -> * -> *}.
StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity (LogInfo p)
returnFinal
filterPatchesByNamesM [AnchoredPath]
_ [] = StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
forall {p :: * -> * -> *}.
StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity (LogInfo p)
returnFinal
filterPatchesByNamesM [AnchoredPath]
fs (s2hp :: Sealed2 (PatchInfoAndG p)
s2hp@(Sealed2 PatchInfoAndG p wX wY
hp) : [Sealed2 (PatchInfoAndG p)]
ps) = do
(Maybe Int
count, [(AnchoredPath, AnchoredPath)]
renames) <- StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(Maybe Int, [(AnchoredPath, AnchoredPath)])
forall s (m :: * -> *). MonadState s m => m s
get
case Maybe Int
count of
Just Int
c | Int
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
forall {p :: * -> * -> *}.
StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity (LogInfo p)
returnFinal
Maybe Int
_ ->
case PatchInfoAndG p wX wY -> Maybe (p wX wY)
forall (p :: * -> * -> *) wA wB.
PatchInfoAndG p wA wB -> Maybe (p wA wB)
hopefullyM PatchInfoAndG p wX wY
hp of
Maybe (p wX wY)
Nothing -> do
let err :: Doc
err = String -> Doc
text String
"Can't find patches prior to:"
Doc -> Doc -> Doc
$$ PatchInfo -> Doc
displayPatchInfo (PatchInfoAndG p wX wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAndG p wX wY
hp)
LogInfo (PatchInfoAndG p)
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
forall a.
a -> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)]
-> Maybe Doc
-> LogInfo (PatchInfoAndG p)
forall (p :: * -> * -> *).
[(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
LogInfo [] [(AnchoredPath, AnchoredPath)]
renames (Doc -> Maybe Doc
forall a. a -> Maybe a
Just Doc
err))
Just p wX wY
p ->
case Maybe [(AnchoredPath, AnchoredPath)]
-> [AnchoredPath]
-> Invertible p wY wX
-> (Bool, [AnchoredPath], [AnchoredPath],
[(AnchoredPath, AnchoredPath)])
forall (p :: * -> * -> *) wX wY.
(Apply p, ApplyState p ~ Tree) =>
Maybe [(AnchoredPath, AnchoredPath)]
-> [AnchoredPath]
-> p wX wY
-> (Bool, [AnchoredPath], [AnchoredPath],
[(AnchoredPath, AnchoredPath)])
lookTouch ([(AnchoredPath, AnchoredPath)]
-> Maybe [(AnchoredPath, AnchoredPath)]
forall a. a -> Maybe a
Just [(AnchoredPath, AnchoredPath)]
renames) [AnchoredPath]
fs (Invertible p wX wY -> Invertible p wY wX
forall wX wY. Invertible p wX wY -> Invertible p wY wX
forall (p :: * -> * -> *) wX wY. Invert p => p wX wY -> p wY wX
invert (p wX wY -> Invertible p wX wY
forall (p :: * -> * -> *) wX wY. p wX wY -> Invertible p wX wY
mkInvertible p wX wY
p)) of
(Bool
True, [AnchoredPath]
affected, [], [(AnchoredPath, AnchoredPath)]
renames') ->
LogInfo (PatchInfoAndG p)
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
forall a.
a -> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)]
-> Maybe Doc
-> LogInfo (PatchInfoAndG p)
forall (p :: * -> * -> *).
[(Sealed2 p, [AnchoredPath])]
-> [(AnchoredPath, AnchoredPath)] -> Maybe Doc -> LogInfo p
LogInfo [(Sealed2 (PatchInfoAndG p)
s2hp, [AnchoredPath]
affected)] [(AnchoredPath, AnchoredPath)]
renames' Maybe Doc
forall a. Maybe a
Nothing)
(Bool
True, [AnchoredPath]
affected, [AnchoredPath]
fs', [(AnchoredPath, AnchoredPath)]
renames') -> do
let sub1Mb :: f b -> f b
sub1Mb f b
c = b -> b -> b
forall a. Num a => a -> a -> a
subtract b
1 (b -> b) -> f b -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f b
c
((Maybe Int, [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)]))
-> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (((Maybe Int, [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)]))
-> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity ())
-> ((Maybe Int, [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)]))
-> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity ()
forall a b. (a -> b) -> a -> b
$ \(Maybe Int
c, [(AnchoredPath, AnchoredPath)]
_) -> (Maybe Int -> Maybe Int
forall {f :: * -> *} {b}. (Functor f, Num b) => f b -> f b
sub1Mb Maybe Int
c, [(AnchoredPath, AnchoredPath)]
renames')
LogInfo (PatchInfoAndG p)
rest <- [AnchoredPath]
-> [Sealed2 (PatchInfoAndG p)]
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
filterPatchesByNamesM [AnchoredPath]
fs' [Sealed2 (PatchInfoAndG p)]
ps
LogInfo (PatchInfoAndG p)
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
forall a.
a -> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (LogInfo (PatchInfoAndG p)
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p)))
-> LogInfo (PatchInfoAndG p)
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
forall a b. (a -> b) -> a -> b
$ LogInfo (PatchInfoAndG p)
rest {
liPatches = (s2hp, affected) : liPatches rest
}
(Bool
False, [AnchoredPath]
_, [AnchoredPath]
fs', [(AnchoredPath, AnchoredPath)]
renames') -> do
((Maybe Int, [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)]))
-> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (((Maybe Int, [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)]))
-> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity ())
-> ((Maybe Int, [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)]))
-> StateT (Maybe Int, [(AnchoredPath, AnchoredPath)]) Identity ()
forall a b. (a -> b) -> a -> b
$ ([(AnchoredPath, AnchoredPath)] -> [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)])
-> (Maybe Int, [(AnchoredPath, AnchoredPath)])
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ([(AnchoredPath, AnchoredPath)]
-> [(AnchoredPath, AnchoredPath)] -> [(AnchoredPath, AnchoredPath)]
forall a b. a -> b -> a
const [(AnchoredPath, AnchoredPath)]
renames')
[AnchoredPath]
-> [Sealed2 (PatchInfoAndG p)]
-> StateT
(Maybe Int, [(AnchoredPath, AnchoredPath)])
Identity
(LogInfo (PatchInfoAndG p))
filterPatchesByNamesM [AnchoredPath]
fs' [Sealed2 (PatchInfoAndG p)]
ps
changelog :: forall p wStart wX
. ( ShowPatch p, PatchListFormat p
, Summary p, HasDeps p, PrimDetails (PrimOf p)
)
=> [DarcsFlag] -> RL (PatchInfoAndG p) wStart wX
-> LogInfo (PatchInfoAndG p)
-> Doc
changelog :: forall (p :: * -> * -> *) wStart wX.
(ShowPatch p, PatchListFormat p, Summary p, HasDeps p,
PrimDetails (PrimOf p)) =>
[DarcsFlag]
-> RL (PatchInfoAndG p) wStart wX
-> LogInfo (PatchInfoAndG p)
-> Doc
changelog [DarcsFlag]
opts RL (PatchInfoAndG p) wStart wX
patches LogInfo (PatchInfoAndG p)
li
| PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe ChangesFormat)
PrimDarcsOption (Maybe ChangesFormat)
O.changesFormat PrimDarcsOption (Maybe ChangesFormat)
-> [DarcsFlag] -> Maybe ChangesFormat
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts Maybe ChangesFormat -> Maybe ChangesFormat -> Bool
forall a. Eq a => a -> a -> Bool
== ChangesFormat -> Maybe ChangesFormat
forall a. a -> Maybe a
Just ChangesFormat
O.CountPatches =
String -> Doc
text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ [(Sealed2 (PatchInfoAndG p), [AnchoredPath])] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([(Sealed2 (PatchInfoAndG p), [AnchoredPath])] -> Int)
-> [(Sealed2 (PatchInfoAndG p), [AnchoredPath])] -> Int
forall a b. (a -> b) -> a -> b
$ LogInfo (PatchInfoAndG p)
-> [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
forall (p :: * -> * -> *).
LogInfo p -> [(Sealed2 p, [AnchoredPath])]
liPatches LogInfo (PatchInfoAndG p)
li
| [DarcsFlag] -> Bool
hasXmlOutput [DarcsFlag]
opts = Doc
xml_changelog
| WithSummary -> Bool
forall a. YesNo a => a -> Bool
O.yes (PrimOptSpec DarcsOptDescr DarcsFlag a WithSummary
PrimDarcsOption WithSummary
O.withSummary PrimDarcsOption WithSummary -> [DarcsFlag] -> WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) Bool -> Bool -> Bool
|| [DarcsFlag] -> Bool
verbose [DarcsFlag]
opts =
[Doc] -> Doc
vsep ((Sealed2 (PatchInfoAndG p) -> Doc)
-> [Sealed2 (PatchInfoAndG p)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ((Sealed2 (PatchInfoAndG p) -> Doc)
-> Sealed2 (PatchInfoAndG p) -> Doc
number_patch Sealed2 (PatchInfoAndG p) -> Doc
change_with_summary) [Sealed2 (PatchInfoAndG p)]
ps) Doc -> Doc -> Doc
$$ Doc
mbErr
| Bool
otherwise = [Doc] -> Doc
vsep ((Sealed2 (PatchInfoAndG p) -> Doc)
-> [Sealed2 (PatchInfoAndG p)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map ((Sealed2 (PatchInfoAndG p) -> Doc)
-> Sealed2 (PatchInfoAndG p) -> Doc
number_patch Sealed2 (PatchInfoAndG p) -> Doc
description') [Sealed2 (PatchInfoAndG p)]
ps) Doc -> Doc -> Doc
$$ Doc
mbErr
where ps_and_fs :: [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
ps_and_fs = LogInfo (PatchInfoAndG p)
-> [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
forall (p :: * -> * -> *).
LogInfo p -> [(Sealed2 p, [AnchoredPath])]
liPatches LogInfo (PatchInfoAndG p)
li
mbErr :: Doc
mbErr = Doc -> Maybe Doc -> Doc
forall a. a -> Maybe a -> a
fromMaybe Doc
forall a. Monoid a => a
mempty (LogInfo (PatchInfoAndG p) -> Maybe Doc
forall (p :: * -> * -> *). LogInfo p -> Maybe Doc
liErrorMsg LogInfo (PatchInfoAndG p)
li)
change_with_summary :: Sealed2 (PatchInfoAndG p) -> Doc
change_with_summary :: Sealed2 (PatchInfoAndG p) -> Doc
change_with_summary (Sealed2 PatchInfoAndG p wX wY
hp)
| Just p wX wY
p <- PatchInfoAndG p wX wY -> Maybe (p wX wY)
forall (p :: * -> * -> *) wA wB.
PatchInfoAndG p wA wB -> Maybe (p wA wB)
hopefullyM PatchInfoAndG p wX wY
hp =
if PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe ChangesFormat)
PrimDarcsOption (Maybe ChangesFormat)
O.changesFormat PrimDarcsOption (Maybe ChangesFormat)
-> [DarcsFlag] -> Maybe ChangesFormat
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts Maybe ChangesFormat -> Maybe ChangesFormat -> Bool
forall a. Eq a => a -> a -> Bool
== ChangesFormat -> Maybe ChangesFormat
forall a. a -> Maybe a
Just ChangesFormat
O.MachineReadable
then ShowPatchFor -> p wX wY -> Doc
forall wX wY. ShowPatchFor -> p wX wY -> Doc
forall (p :: * -> * -> *) wX wY.
ShowPatchBasic p =>
ShowPatchFor -> p wX wY -> Doc
showPatch ShowPatchFor
ForStorage p wX wY
p
else Verbosity -> WithSummary -> p wX wY -> Doc
forall (p :: * -> * -> *) wX wY.
ShowPatch p =>
Verbosity -> WithSummary -> p wX wY -> Doc
showFriendly (PrimOptSpec DarcsOptDescr DarcsFlag a Verbosity
PrimDarcsOption Verbosity
verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) (PrimOptSpec DarcsOptDescr DarcsFlag a WithSummary
PrimDarcsOption WithSummary
O.withSummary PrimDarcsOption WithSummary -> [DarcsFlag] -> WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) p wX wY
p
| Bool
otherwise = PatchInfoAndG p wX wY -> Doc
forall wX wY. PatchInfoAndG p wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description PatchInfoAndG p wX wY
hp Doc -> Doc -> Doc
$$ Doc -> Doc
indent (String -> Doc
text String
"[this patch is unavailable]")
xml_changelog :: Doc
xml_changelog = [Doc] -> Doc
vcat
[ String -> Doc
text String
"<changelog>"
, [Doc] -> Doc
vcat [Doc]
xml_created_as
, [Doc] -> Doc
vcat [Doc]
xml_changes
, String -> Doc
text String
"</changelog>"
]
xml_with_summary :: Sealed2 (PatchInfoAndG p) -> Doc
xml_with_summary :: Sealed2 (PatchInfoAndG p) -> Doc
xml_with_summary (Sealed2 PatchInfoAndG p wX wY
hp) | Just p wX wY
p <- PatchInfoAndG p wX wY -> Maybe (p wX wY)
forall (p :: * -> * -> *) wA wB.
PatchInfoAndG p wA wB -> Maybe (p wA wB)
hopefullyM PatchInfoAndG p wX wY
hp =
let
deps :: [PatchInfo]
deps = p wX wY -> [PatchInfo]
forall wX wY. p wX wY -> [PatchInfo]
forall (p :: * -> * -> *) wX wY.
HasDeps p =>
p wX wY -> [PatchInfo]
getdeps p wX wY
p
xmlDependencies :: Doc
xmlDependencies =
String -> Doc
text String
"<explicit_dependencies>"
Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat ((PatchInfo -> Doc) -> [PatchInfo] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Doc -> Doc
indent (Doc -> Doc) -> (PatchInfo -> Doc) -> PatchInfo -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatchInfo -> Doc
toXmlShort) [PatchInfo]
deps)
Doc -> Doc -> Doc
$$ String -> Doc
text String
"</explicit_dependencies>"
summary :: Doc
summary | [PatchInfo]
deps [PatchInfo] -> [PatchInfo] -> Bool
forall a. Eq a => a -> a -> Bool
== [] = Doc -> Doc
indent (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ p wX wY -> Doc
forall (p :: * -> * -> *) wX wY.
(Summary p, PrimDetails (PrimOf p)) =>
p wX wY -> Doc
xmlSummary p wX wY
p
| Bool
otherwise = Doc -> Doc
indent (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Doc
xmlDependencies Doc -> Doc -> Doc
$$ p wX wY -> Doc
forall (p :: * -> * -> *) wX wY.
(Summary p, PrimDetails (PrimOf p)) =>
p wX wY -> Doc
xmlSummary p wX wY
p
in
Doc -> Doc -> Doc
insertBeforeLastline (PatchInfo -> Doc
toXml (PatchInfo -> Doc) -> PatchInfo -> Doc
forall a b. (a -> b) -> a -> b
$ PatchInfoAndG p wX wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAndG p wX wY
hp) Doc
summary
xml_with_summary (Sealed2 PatchInfoAndG p wX wY
hp) = PatchInfo -> Doc
toXml (PatchInfoAndG p wX wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAndG p wX wY
hp)
indent :: Doc -> Doc
indent = String -> Doc -> Doc
prefix String
" "
xml_changes :: [Doc]
xml_changes =
case PrimOptSpec DarcsOptDescr DarcsFlag a WithSummary
PrimDarcsOption WithSummary
O.withSummary PrimDarcsOption WithSummary -> [DarcsFlag] -> WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts of
WithSummary
O.YesSummary -> (Sealed2 (PatchInfoAndG p) -> Doc)
-> [Sealed2 (PatchInfoAndG p)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Sealed2 (PatchInfoAndG p) -> Doc
xml_with_summary [Sealed2 (PatchInfoAndG p)]
ps
WithSummary
O.NoSummary -> (Sealed2 (PatchInfoAndG p) -> Doc)
-> [Sealed2 (PatchInfoAndG p)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (PatchInfo -> Doc
toXml (PatchInfo -> Doc)
-> (Sealed2 (PatchInfoAndG p) -> PatchInfo)
-> Sealed2 (PatchInfoAndG p)
-> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall wX wY. PatchInfoAndG p wX wY -> PatchInfo)
-> Sealed2 (PatchInfoAndG p) -> PatchInfo
forall (a :: * -> * -> *) b.
(forall wX wY. a wX wY -> b) -> Sealed2 a -> b
unseal2 PatchInfoAndG p wX wY -> PatchInfo
forall wX wY. PatchInfoAndG p wX wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info) [Sealed2 (PatchInfoAndG p)]
ps
xml_created_as :: [Doc]
xml_created_as = ((AnchoredPath, AnchoredPath) -> Doc)
-> [(AnchoredPath, AnchoredPath)] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (AnchoredPath, AnchoredPath) -> Doc
create (LogInfo (PatchInfoAndG p) -> [(AnchoredPath, AnchoredPath)]
forall (p :: * -> * -> *).
LogInfo p -> [(AnchoredPath, AnchoredPath)]
liRenames LogInfo (PatchInfoAndG p)
li) where
create :: (AnchoredPath, AnchoredPath) -> Doc
create :: (AnchoredPath, AnchoredPath) -> Doc
create rename :: (AnchoredPath, AnchoredPath)
rename@(AnchoredPath
_, AnchoredPath
as) = PatchInfo -> (AnchoredPath, AnchoredPath) -> Doc
createdAsXml (AnchoredPath -> PatchInfo
first_change_of AnchoredPath
as) (AnchoredPath, AnchoredPath)
rename
reorderer :: [a] -> [a]
reorderer = if Bool -> Bool
not (PrimOptSpec DarcsOptDescr DarcsFlag a Bool
PrimDarcsOption Bool
changesReverse PrimDarcsOption Bool -> [DarcsFlag] -> Bool
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) then [a] -> [a]
forall a. [a] -> [a]
reverse else [a] -> [a]
forall a. a -> a
id
oldest_first_ps_and_fs :: [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
oldest_first_ps_and_fs = [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
-> [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
forall a. [a] -> [a]
reorderer [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
ps_and_fs
couldnt_find :: AnchoredPath -> a
couldnt_find AnchoredPath
fn = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Couldn't find first patch affecting " String -> String -> String
forall a. [a] -> [a] -> [a]
++
(AnchoredPath -> String
displayPath AnchoredPath
fn) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" in ps_and_fs"
mb_first_change_of :: AnchoredPath -> Maybe (Sealed2 (PatchInfoAndG p), [AnchoredPath])
mb_first_change_of AnchoredPath
fn = ((Sealed2 (PatchInfoAndG p), [AnchoredPath]) -> Bool)
-> [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
-> Maybe (Sealed2 (PatchInfoAndG p), [AnchoredPath])
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((AnchoredPath
fn AnchoredPath -> [AnchoredPath] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`) ([AnchoredPath] -> Bool)
-> ((Sealed2 (PatchInfoAndG p), [AnchoredPath]) -> [AnchoredPath])
-> (Sealed2 (PatchInfoAndG p), [AnchoredPath])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sealed2 (PatchInfoAndG p), [AnchoredPath]) -> [AnchoredPath]
forall a b. (a, b) -> b
snd) [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
oldest_first_ps_and_fs
find_first_change_of :: AnchoredPath -> (Sealed2 (PatchInfoAndG p), [AnchoredPath])
find_first_change_of AnchoredPath
fn = (Sealed2 (PatchInfoAndG p), [AnchoredPath])
-> Maybe (Sealed2 (PatchInfoAndG p), [AnchoredPath])
-> (Sealed2 (PatchInfoAndG p), [AnchoredPath])
forall a. a -> Maybe a -> a
fromMaybe (AnchoredPath -> (Sealed2 (PatchInfoAndG p), [AnchoredPath])
forall {a}. AnchoredPath -> a
couldnt_find AnchoredPath
fn)
(AnchoredPath -> Maybe (Sealed2 (PatchInfoAndG p), [AnchoredPath])
mb_first_change_of AnchoredPath
fn)
first_change_of :: AnchoredPath -> PatchInfo
first_change_of :: AnchoredPath -> PatchInfo
first_change_of = (forall wX wY. PatchInfoAndG p wX wY -> PatchInfo)
-> Sealed2 (PatchInfoAndG p) -> PatchInfo
forall (a :: * -> * -> *) b.
(forall wX wY. a wX wY -> b) -> Sealed2 a -> b
unseal2 PatchInfoAndG p wX wY -> PatchInfo
forall wX wY. PatchInfoAndG p wX wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info (Sealed2 (PatchInfoAndG p) -> PatchInfo)
-> (AnchoredPath -> Sealed2 (PatchInfoAndG p))
-> AnchoredPath
-> PatchInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sealed2 (PatchInfoAndG p), [AnchoredPath])
-> Sealed2 (PatchInfoAndG p)
forall a b. (a, b) -> a
fst ((Sealed2 (PatchInfoAndG p), [AnchoredPath])
-> Sealed2 (PatchInfoAndG p))
-> (AnchoredPath -> (Sealed2 (PatchInfoAndG p), [AnchoredPath]))
-> AnchoredPath
-> Sealed2 (PatchInfoAndG p)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredPath -> (Sealed2 (PatchInfoAndG p), [AnchoredPath])
find_first_change_of
number_patch :: (Sealed2 (PatchInfoAndG p) -> Doc)
-> Sealed2 (PatchInfoAndG p) -> Doc
number_patch Sealed2 (PatchInfoAndG p) -> Doc
f Sealed2 (PatchInfoAndG p)
x = if PrimOptSpec DarcsOptDescr DarcsFlag a (Maybe ChangesFormat)
PrimDarcsOption (Maybe ChangesFormat)
O.changesFormat PrimDarcsOption (Maybe ChangesFormat)
-> [DarcsFlag] -> Maybe ChangesFormat
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts Maybe ChangesFormat -> Maybe ChangesFormat -> Bool
forall a. Eq a => a -> a -> Bool
== ChangesFormat -> Maybe ChangesFormat
forall a. a -> Maybe a
Just ChangesFormat
O.NumberPatches
then case Sealed2 (PatchInfoAndG p) -> Maybe Int
get_number Sealed2 (PatchInfoAndG p)
x of
Just Int
n -> String -> Doc
text (Int -> String
forall a. Show a => a -> String
show Int
nString -> String -> String
forall a. [a] -> [a] -> [a]
++String
":") Doc -> Doc -> Doc
<+> Sealed2 (PatchInfoAndG p) -> Doc
f Sealed2 (PatchInfoAndG p)
x
Maybe Int
Nothing -> Sealed2 (PatchInfoAndG p) -> Doc
f Sealed2 (PatchInfoAndG p)
x
else Sealed2 (PatchInfoAndG p) -> Doc
f Sealed2 (PatchInfoAndG p)
x
get_number :: Sealed2 (PatchInfoAndG p) -> Maybe Int
get_number :: Sealed2 (PatchInfoAndG p) -> Maybe Int
get_number (Sealed2 PatchInfoAndG p wX wY
y) = Int -> RL (PatchInfoAndG p) wStart wX -> Maybe Int
forall wY. Int -> RL (PatchInfoAndG p) wStart wY -> Maybe Int
gn Int
1 RL (PatchInfoAndG p) wStart wX
patches
where iy :: PatchInfo
iy = PatchInfoAndG p wX wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAndG p wX wY
y
gn :: Int -> RL (PatchInfoAndG p) wStart wY -> Maybe Int
gn :: forall wY. Int -> RL (PatchInfoAndG p) wStart wY -> Maybe Int
gn Int
n (RL (PatchInfoAndG p) wStart wY
bs:<:PatchInfoAndG p wY wY
b) | Int -> PatchInfo -> PatchInfo
forall a b. a -> b -> b
seq Int
n (PatchInfoAndG p wY wY -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info PatchInfoAndG p wY wY
b) PatchInfo -> PatchInfo -> Bool
forall a. Eq a => a -> a -> Bool
== PatchInfo
iy = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n
| Bool
otherwise = Int -> RL (PatchInfoAndG p) wStart wY -> Maybe Int
forall wY. Int -> RL (PatchInfoAndG p) wStart wY -> Maybe Int
gn (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) RL (PatchInfoAndG p) wStart wY
bs
gn Int
_ RL (PatchInfoAndG p) wStart wY
NilRL = Maybe Int
forall a. Maybe a
Nothing
ps :: [Sealed2 (PatchInfoAndG p)]
ps = ((Sealed2 (PatchInfoAndG p), [AnchoredPath])
-> Sealed2 (PatchInfoAndG p))
-> [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
-> [Sealed2 (PatchInfoAndG p)]
forall a b. (a -> b) -> [a] -> [b]
map (Sealed2 (PatchInfoAndG p), [AnchoredPath])
-> Sealed2 (PatchInfoAndG p)
forall a b. (a, b) -> a
fst [(Sealed2 (PatchInfoAndG p), [AnchoredPath])]
ps_and_fs
description' :: Sealed2 (PatchInfoAndG p) -> Doc
description' = (forall wX wY. PatchInfoAndG p wX wY -> Doc)
-> Sealed2 (PatchInfoAndG p) -> Doc
forall (a :: * -> * -> *) b.
(forall wX wY. a wX wY -> b) -> Sealed2 a -> b
unseal2 PatchInfoAndG p wX wY -> Doc
forall wX wY. PatchInfoAndG p wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> Doc
description
logContext :: [DarcsFlag] -> IO ()
logContext :: [DarcsFlag] -> IO ()
logContext [DarcsFlag]
opts = do
let repodir :: String
repodir = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"." (Maybe String -> String) -> Maybe String -> String
forall a b. (a -> b) -> a -> b
$ [DarcsFlag] -> Maybe String
getRepourl [DarcsFlag]
opts
UseCache -> String -> RepoJob 'RO () -> IO ()
forall a. UseCache -> String -> RepoJob 'RO a -> IO a
withRepositoryLocation (PrimOptSpec DarcsOptDescr DarcsFlag a UseCache
PrimDarcsOption UseCache
useCache PrimDarcsOption UseCache -> [DarcsFlag] -> UseCache
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
opts) String
repodir (RepoJob 'RO () -> IO ()) -> RepoJob 'RO () -> IO ()
forall a b. (a -> b) -> a -> b
$ TreePatchJob 'RO () -> RepoJob 'RO ()
forall (rt :: AccessType) a. TreePatchJob rt a -> RepoJob rt a
RepoJob (TreePatchJob 'RO () -> RepoJob 'RO ())
-> TreePatchJob 'RO () -> RepoJob 'RO ()
forall a b. (a -> b) -> a -> b
$ \Repository 'RO p wU wR
repository -> do
(PatchSet p Origin wZ
_ :> RL (PatchInfoAnd p) wZ wR
ps) <- PatchSet p Origin wR
-> (:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR
forall (p :: * -> * -> *) wX wY.
PatchSet p wX wY -> (:>) (PatchSet p) (RL (PatchInfoAnd p)) wX wY
contextPatches (PatchSet p Origin wR
-> (:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR)
-> IO (PatchSet p Origin wR)
-> IO ((:>) (PatchSet p) (RL (PatchInfoAnd p)) Origin wR)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Repository 'RO p wU wR -> IO (PatchSet p Origin wR)
forall (p :: * -> * -> *) (rt :: AccessType) wU wR.
RepoPatch p =>
Repository rt p wU wR -> IO (PatchSet p Origin wR)
readPatches Repository 'RO p wU wR
repository
let header :: Doc
header = String -> Doc
text String
"\nContext:\n"
Printers -> Doc -> IO ()
viewDocWith Printers
simplePrinters (Doc -> IO ()) -> Doc -> IO ()
forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
vsep
(Doc
header Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (forall wW wZ. PatchInfoAnd p wW wZ -> Doc)
-> RL (PatchInfoAnd p) wZ wR -> [Doc]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> RL a wX wY -> [b]
mapRL (ShowPatchFor -> PatchInfo -> Doc
showPatchInfo ShowPatchFor
ForStorage (PatchInfo -> Doc)
-> (PatchInfoAnd p wW wZ -> PatchInfo)
-> PatchInfoAnd p wW wZ
-> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatchInfoAnd p wW wZ -> PatchInfo
forall (p :: * -> * -> *) wA wB. PatchInfoAndG p wA wB -> PatchInfo
info) RL (PatchInfoAnd p) wZ wR
ps)
changes :: DarcsCommand
changes :: DarcsCommand
changes = String -> Maybe DarcsCommand -> DarcsCommand -> DarcsCommand
commandAlias String
"changes" Maybe DarcsCommand
forall a. Maybe a
Nothing DarcsCommand
log
createdAsXml :: PatchInfo -> (AnchoredPath, AnchoredPath) -> Doc
createdAsXml :: PatchInfo -> (AnchoredPath, AnchoredPath) -> Doc
createdAsXml PatchInfo
pinfo (AnchoredPath
current, AnchoredPath
createdAs) =
String -> Doc
text String
"<created_as current_name='"
Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
escapeXML (AnchoredPath -> String
displayPath AnchoredPath
current)
Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text String
"' original_name='"
Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
escapeXML (AnchoredPath -> String
displayPath AnchoredPath
createdAs)
Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
<> String -> Doc
text String
"'>"
Doc -> Doc -> Doc
$$ PatchInfo -> Doc
toXml PatchInfo
pinfo
Doc -> Doc -> Doc
$$ String -> Doc
text String
"</created_as>"
logPatchSelOpts :: [DarcsFlag] -> S.PatchSelectionOptions
logPatchSelOpts :: [DarcsFlag] -> PatchSelectionOptions
logPatchSelOpts [DarcsFlag]
flags = S.PatchSelectionOptions
{ verbosity :: Verbosity
S.verbosity = PrimOptSpec DarcsOptDescr DarcsFlag a Verbosity
PrimDarcsOption Verbosity
verbosity PrimDarcsOption Verbosity -> [DarcsFlag] -> Verbosity
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags
, matchFlags :: [MatchFlag]
S.matchFlags = MatchOption -> [DarcsFlag] -> [MatchFlag]
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
parseFlags PrimOptSpec DarcsOptDescr DarcsFlag a [MatchFlag]
MatchOption
O.matchSeveralOrRange [DarcsFlag]
flags
, interactive :: Bool
S.interactive = Bool -> [DarcsFlag] -> Bool
isInteractive Bool
False [DarcsFlag]
flags
, selectDeps :: SelectDeps
S.selectDeps = SelectDeps
O.PromptDeps
, withSummary :: WithSummary
S.withSummary = PrimOptSpec DarcsOptDescr DarcsFlag a WithSummary
PrimDarcsOption WithSummary
O.withSummary PrimDarcsOption WithSummary -> [DarcsFlag] -> WithSummary
forall (d :: * -> *) f v.
(forall a. PrimOptSpec d f a v) -> [f] -> v
? [DarcsFlag]
flags
}