multiple -m second try
Test suite passes this time. When committing the adjusted branch, use the old method to make a message that old git-annex can consume. Also made the code accept the new message, so that eventually commitTreeExactMessage can be removed. Sponsored-by: Kevin Mueller on Patreon
This commit is contained in:
parent
69546f73ca
commit
2c73845d90
15 changed files with 77 additions and 41 deletions
|
@ -468,19 +468,30 @@ commitAdjustedTree' treesha (BasisBranch basis) parents =
|
|||
(commitAuthorMetaData basiscommit)
|
||||
(commitCommitterMetaData basiscommit)
|
||||
(mkcommit cmode)
|
||||
mkcommit cmode = Git.Branch.commitTree cmode
|
||||
-- Make sure that the exact message is used in the commit,
|
||||
-- since that message is looked for later.
|
||||
-- After git-annex 10.20240227, it's possible to use
|
||||
-- commitTree instead of this, but this is being kept
|
||||
-- for some time, for compatability with older versions.
|
||||
mkcommit cmode = Git.Branch.commitTreeExactMessage cmode
|
||||
adjustedBranchCommitMessage parents treesha
|
||||
|
||||
{- This message should never be changed. -}
|
||||
adjustedBranchCommitMessage :: String
|
||||
adjustedBranchCommitMessage = "git-annex adjusted branch"
|
||||
|
||||
{- Allow for a trailing newline after the message. -}
|
||||
hasAdjustedBranchCommitMessage :: Commit -> Bool
|
||||
hasAdjustedBranchCommitMessage c =
|
||||
dropWhileEnd (\x -> x == '\n' || x == '\r') (commitMessage c)
|
||||
== adjustedBranchCommitMessage
|
||||
|
||||
findAdjustingCommit :: AdjBranch -> Annex (Maybe Commit)
|
||||
findAdjustingCommit (AdjBranch b) = go =<< catCommit b
|
||||
where
|
||||
go Nothing = return Nothing
|
||||
go (Just c)
|
||||
| commitMessage c == adjustedBranchCommitMessage = return (Just c)
|
||||
| hasAdjustedBranchCommitMessage c = return (Just c)
|
||||
| otherwise = case commitParent c of
|
||||
[p] -> go =<< catCommit p
|
||||
_ -> return Nothing
|
||||
|
@ -540,7 +551,7 @@ propigateAdjustedCommits' warnwhendiverged origbranch adj _commitsprevented =
|
|||
return (Right parent)
|
||||
go origsha parent pastadjcommit (sha:l) = catCommit sha >>= \case
|
||||
Just c
|
||||
| commitMessage c == adjustedBranchCommitMessage ->
|
||||
| hasAdjustedBranchCommitMessage c ->
|
||||
go origsha parent True l
|
||||
| pastadjcommit ->
|
||||
reverseAdjustedCommit parent adj (sha, c) origbranch
|
||||
|
@ -577,7 +588,7 @@ reverseAdjustedCommit commitparent adj (csha, basiscommit) origbranch
|
|||
(commitAuthorMetaData basiscommit)
|
||||
(commitCommitterMetaData basiscommit) $
|
||||
Git.Branch.commitTree cmode
|
||||
(commitMessage basiscommit)
|
||||
[commitMessage basiscommit]
|
||||
[commitparent] treesha
|
||||
return (Right revadjcommit)
|
||||
|
||||
|
|
|
@ -153,7 +153,8 @@ mergeToAdjustedBranch tomerge (origbranch, adj) mergeconfig canresolvemerge comm
|
|||
then do
|
||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||
c <- inRepo $ Git.Branch.commitTree cmode
|
||||
("Merged " ++ fromRef tomerge) [adjmergecommit]
|
||||
["Merged " ++ fromRef tomerge]
|
||||
[adjmergecommit]
|
||||
(commitTree currentcommit)
|
||||
inRepo $ Git.Branch.update "updating adjusted branch" currbranch c
|
||||
propigateAdjustedCommits origbranch adj
|
||||
|
|
|
@ -945,9 +945,9 @@ rememberTreeishLocked treeish graftpoint jl = do
|
|||
addedt <- inRepo $ Git.Tree.graftTree treeish graftpoint origtree
|
||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||
c <- inRepo $ Git.Branch.commitTree cmode
|
||||
"graft" [branchref] addedt
|
||||
["graft"] [branchref] addedt
|
||||
c' <- inRepo $ Git.Branch.commitTree cmode
|
||||
"graft cleanup" [c] origtree
|
||||
["graft cleanup"] [c] origtree
|
||||
inRepo $ Git.Branch.update' fullname c'
|
||||
-- The tree in c' is the same as the tree in branchref,
|
||||
-- and the index was updated to that above, so it's safe to
|
||||
|
|
|
@ -86,7 +86,7 @@ data ImportCommitConfig = ImportCommitConfig
|
|||
{ importCommitTracking :: Maybe Sha
|
||||
-- ^ Current commit on the remote tracking branch.
|
||||
, importCommitMode :: Git.Branch.CommitMode
|
||||
, importCommitMessage :: String
|
||||
, importCommitMessages :: [String]
|
||||
}
|
||||
|
||||
{- Buils a commit for an import from a special remote.
|
||||
|
@ -251,7 +251,7 @@ buildImportCommit' remote importcommitconfig mtrackingcommit imported@(History t
|
|||
|
||||
mkcommit parents tree = inRepo $ Git.Branch.commitTree
|
||||
(importCommitMode importcommitconfig)
|
||||
(importCommitMessage importcommitconfig)
|
||||
(importCommitMessages importcommitconfig)
|
||||
parents
|
||||
tree
|
||||
|
||||
|
|
|
@ -77,7 +77,7 @@ makeRemoteTrackingBranchMergeCommit' commitsha importedhistory treesha = do
|
|||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||
inRepo $ Git.Branch.commitTree
|
||||
cmode
|
||||
"remote tracking branch"
|
||||
["remote tracking branch"]
|
||||
[commitsha, importedhistory]
|
||||
treesha
|
||||
|
||||
|
|
|
@ -577,7 +577,7 @@ updateView view madj = do
|
|||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||
let msg = "updated " ++ fromRef (branchView view madj)
|
||||
let parent = catMaybes [oldcommit]
|
||||
inRepo (Git.Branch.commitTree cmode msg parent newtree)
|
||||
inRepo (Git.Branch.commitTree cmode [msg] parent newtree)
|
||||
else return Nothing
|
||||
|
||||
{- Diff between currently checked out branch and staged changes, and
|
||||
|
|
|
@ -13,6 +13,8 @@ git-annex (10.20240228) UNRELEASED; urgency=medium
|
|||
the same repository.
|
||||
* Windows: Fix escaping output to terminal when using old
|
||||
versions of MinTTY.
|
||||
* sync, assist, import: Allow -m option to be specified multiple
|
||||
times, to provide additional paragraphs for the commit message.
|
||||
|
||||
-- Joey Hess <id@joeyh.name> Tue, 27 Feb 2024 13:07:10 -0400
|
||||
|
||||
|
|
|
@ -189,7 +189,7 @@ seek o = withOtherTmp $ \tmpdir -> do
|
|||
liftIO $ removeWhenExistsWith removeLink tmpindex
|
||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||
cmessage <- Annex.Branch.commitMessage
|
||||
c <- inRepo $ Git.commitTree cmode cmessage [] t
|
||||
c <- inRepo $ Git.commitTree cmode [cmessage] [] t
|
||||
liftIO $ putStrLn (fromRef c)
|
||||
where
|
||||
ww = WarnUnmatchLsFiles "filter-branch"
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{- git-annex command
|
||||
-
|
||||
- Copyright 2012-2021 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2012-2024 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
@ -70,7 +70,7 @@ data ImportOptions
|
|||
, importToSubDir :: Maybe FilePath
|
||||
, importContent :: Bool
|
||||
, checkGitIgnoreOption :: CheckGitIgnore
|
||||
, messageOption :: Maybe String
|
||||
, messageOption :: [String]
|
||||
}
|
||||
|
||||
optParser :: CmdParamsDesc -> Parser ImportOptions
|
||||
|
@ -82,7 +82,7 @@ optParser desc = do
|
|||
)
|
||||
dupmode <- fromMaybe Default <$> optional duplicateModeParser
|
||||
ic <- Command.Add.checkGitIgnoreSwitch
|
||||
message <- optional (strOption
|
||||
message <- many (strOption
|
||||
( long "message" <> short 'm' <> metavar "MSG"
|
||||
<> help "commit message"
|
||||
))
|
||||
|
@ -322,8 +322,8 @@ verifyExisting key destfile (yes, no) = do
|
|||
verifyEnoughCopiesToDrop [] key Nothing needcopies mincopies [] preverified tocheck
|
||||
(const yes) no
|
||||
|
||||
seekRemote :: Remote -> Branch -> Maybe TopFilePath -> Bool -> CheckGitIgnore -> Maybe String -> CommandSeek
|
||||
seekRemote remote branch msubdir importcontent ci mimportmessage = do
|
||||
seekRemote :: Remote -> Branch -> Maybe TopFilePath -> Bool -> CheckGitIgnore -> [String] -> CommandSeek
|
||||
seekRemote remote branch msubdir importcontent ci importmessages = do
|
||||
importtreeconfig <- case msubdir of
|
||||
Nothing -> return ImportTree
|
||||
Just subdir ->
|
||||
|
@ -336,7 +336,7 @@ seekRemote remote branch msubdir importcontent ci mimportmessage = do
|
|||
|
||||
trackingcommit <- fromtrackingbranch Git.Ref.sha
|
||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||
let importcommitconfig = ImportCommitConfig trackingcommit cmode importmessage
|
||||
let importcommitconfig = ImportCommitConfig trackingcommit cmode importmessages'
|
||||
let commitimport = commitRemote remote branch tb trackingcommit importtreeconfig importcommitconfig
|
||||
|
||||
importabletvar <- liftIO $ newTVarIO Nothing
|
||||
|
@ -353,9 +353,9 @@ seekRemote remote branch msubdir importcontent ci mimportmessage = do
|
|||
includeCommandAction $
|
||||
commitimport imported
|
||||
where
|
||||
importmessage = fromMaybe
|
||||
("import from " ++ Remote.name remote)
|
||||
mimportmessage
|
||||
importmessages'
|
||||
| null importmessages = ["import from " ++ Remote.name remote]
|
||||
| otherwise = importmessages
|
||||
|
||||
tb = mkRemoteTrackingBranch remote branch
|
||||
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{- git-annex command
|
||||
-
|
||||
- Copyright 2011 Joachim Breitner <mail@joachim-breitner.de>
|
||||
- Copyright 2011-2023 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2011-2024 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
@ -105,7 +105,7 @@ data SyncOptions = SyncOptions
|
|||
, notOnlyAnnexOption :: Bool
|
||||
, commitOption :: Bool
|
||||
, noCommitOption :: Bool
|
||||
, messageOption :: Maybe String
|
||||
, messageOption :: [String]
|
||||
, pullOption :: Bool
|
||||
, pushOption :: Bool
|
||||
, contentOption :: Maybe Bool
|
||||
|
@ -125,7 +125,7 @@ instance Default SyncOptions where
|
|||
, notOnlyAnnexOption = False
|
||||
, commitOption = False
|
||||
, noCommitOption = False
|
||||
, messageOption = Nothing
|
||||
, messageOption = []
|
||||
, pullOption = False
|
||||
, pushOption = False
|
||||
, contentOption = Just False
|
||||
|
@ -169,8 +169,8 @@ optParser mode desc = SyncOptions
|
|||
( long "no-commit"
|
||||
<> help "avoid git commit"
|
||||
))
|
||||
<*> unlessmode [SyncMode, AssistMode] Nothing
|
||||
(optional (strOption
|
||||
<*> unlessmode [SyncMode, AssistMode] []
|
||||
(many (strOption
|
||||
( long "message" <> short 'm' <> metavar "MSG"
|
||||
<> help "commit message"
|
||||
)))
|
||||
|
@ -402,17 +402,18 @@ syncRemotes' ps available =
|
|||
|
||||
commit :: SyncOptions -> CommandStart
|
||||
commit o = stopUnless shouldcommit $ starting "commit" ai si $ do
|
||||
commitmessage <- maybe commitMsg return (messageOption o)
|
||||
Annex.Branch.commit =<< Annex.Branch.commitMessage
|
||||
mopts <- concatMap (\msg -> [Param "-m", Param msg])
|
||||
<$> if null (messageOption o)
|
||||
then (:[]) <$> commitMsg
|
||||
else pure (messageOption o)
|
||||
next $ do
|
||||
showOutput
|
||||
let cmode = Git.Branch.ManualCommit
|
||||
cquiet <- Git.Branch.CommitQuiet <$> commandProgressDisabled
|
||||
void $ inRepo $ Git.Branch.commitCommand cmode cquiet
|
||||
[ Param "-a"
|
||||
, Param "-m"
|
||||
, Param commitmessage
|
||||
]
|
||||
void $ inRepo $ Git.Branch.commitCommand
|
||||
cmode cquiet
|
||||
([ Param "-a" ] ++ mopts)
|
||||
return True
|
||||
where
|
||||
shouldcommit = notOnlyAnnex o <&&>
|
||||
|
@ -426,7 +427,8 @@ commitMsg :: Annex String
|
|||
commitMsg = do
|
||||
u <- getUUID
|
||||
m <- uuidDescMap
|
||||
return $ "git-annex in " ++ maybe "unknown" fromUUIDDesc (M.lookup u m)
|
||||
return $ "git-annex in "
|
||||
++ maybe "unknown" fromUUIDDesc (M.lookup u m)
|
||||
|
||||
mergeLocal :: [Git.Merge.MergeConfig] -> SyncOptions -> CurrBranch -> CommandStart
|
||||
mergeLocal mergeconfig o currbranch = stopUnless (notOnlyAnnex o) $
|
||||
|
@ -578,7 +580,7 @@ importRemote importcontent o remote currbranch
|
|||
let (branch, subdir) = splitRemoteAnnexTrackingBranchSubdir b
|
||||
if canImportKeys remote importcontent
|
||||
then do
|
||||
Command.Import.seekRemote remote branch subdir importcontent (CheckGitIgnore True) Nothing
|
||||
Command.Import.seekRemote remote branch subdir importcontent (CheckGitIgnore True) []
|
||||
-- Importing generates a branch
|
||||
-- that is not initially connected
|
||||
-- to the current branch, so allow
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{- git branch stuff
|
||||
-
|
||||
- Copyright 2011-2021 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2011-2024 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
@ -178,7 +178,7 @@ commit commitmode allowempty message branch parentrefs repo = do
|
|||
tree <- writeTree repo
|
||||
ifM (cancommit tree)
|
||||
( do
|
||||
sha <- commitTree commitmode message parentrefs tree repo
|
||||
sha <- commitTree commitmode [message] parentrefs tree repo
|
||||
update' branch sha repo
|
||||
return $ Just sha
|
||||
, return Nothing
|
||||
|
@ -207,8 +207,21 @@ writeTreeQuiet repo = extractSha <$> withNullHandle go
|
|||
go nullh = pipeReadStrict' (\p -> p { std_err = UseHandle nullh })
|
||||
[Param "write-tree"] repo
|
||||
|
||||
commitTree :: CommitMode -> String -> [Ref] -> Ref -> Repo -> IO Sha
|
||||
commitTree commitmode message parentrefs tree repo =
|
||||
commitTree :: CommitMode -> [String] -> [Ref] -> Ref -> Repo -> IO Sha
|
||||
commitTree commitmode messages parentrefs tree repo =
|
||||
getSha "commit-tree" $ pipeReadStrict ps repo
|
||||
where
|
||||
ps = [Param "commit-tree", Param (fromRef tree)]
|
||||
++ applyCommitModeForCommitTree commitmode baseparams repo
|
||||
baseparams = map Param $
|
||||
concatMap (\r -> ["-p", fromRef r]) parentrefs
|
||||
++ concatMap (\msg -> ["-m", msg]) messages
|
||||
|
||||
-- commitTree passes the commit message to git with -m, which can cause it
|
||||
-- to get modified slightly (eg adding trailing newline). This variant uses
|
||||
-- the exact commit message that is provided.
|
||||
commitTreeExactMessage :: CommitMode -> String -> [Ref] -> Ref -> Repo -> IO Sha
|
||||
commitTreeExactMessage commitmode message parentrefs tree repo =
|
||||
getSha "commit-tree" $
|
||||
pipeWriteRead ([Param "commit-tree", Param (fromRef tree)] ++ ps)
|
||||
sendmsg repo
|
||||
|
|
|
@ -34,6 +34,9 @@ files that it does not match will instead be added with `git add`.
|
|||
|
||||
Use this option to specify a commit message.
|
||||
|
||||
If multiple -m options are given, their values are concatenated
|
||||
as separate paragraphs.
|
||||
|
||||
* `--content-of=path` `-C path`
|
||||
|
||||
Only add, pull, and push files in the given path.
|
||||
|
|
|
@ -107,6 +107,9 @@ the tree of files on the remote, even when importing into a subdirectory.
|
|||
Use this option to specify a commit message for the changes that have
|
||||
been made to the special remote since the last import from it.
|
||||
|
||||
If multiple -m options are given, their values are concatenated
|
||||
as separate paragraphs.
|
||||
|
||||
# IMPORTING FROM A DIRECTORY
|
||||
|
||||
When run with a path, `git annex import` **moves** files from somewhere outside
|
||||
|
|
|
@ -51,6 +51,9 @@ when syncing with repositories that have preferred content configured.
|
|||
|
||||
Use this option to specify a commit message.
|
||||
|
||||
If multiple -m options are given, their values are concatenated
|
||||
as separate paragraphs.
|
||||
|
||||
* `--pull`, `--no-pull`
|
||||
|
||||
Use this option to disable pulling.
|
||||
|
|
|
@ -1,6 +1,4 @@
|
|||
git-annex sync etc -m should be able to be specified multiple times. In git
|
||||
commit, multiple -m can be used to make a multiparagraph commit. --[[Joey]]
|
||||
|
||||
> I got this implemented, but it caused a reversion. See
|
||||
> [[!commit a8dd85ea5a9f8515819db04b9f1d154488193e7d]]
|
||||
> for what needs to be done on this next. --[[Joey]]
|
||||
> [[done]]
|
||||
|
|
Loading…
Reference in a new issue