Revert "multiple -m"
This reverts commit cee12f6a2f
.
This commit broke git-annex init run in a repo that was cloned from a
repo with an adjusted branch checked out.
The problem is that findAdjustingCommit was not able to identify the
commit that created the adjusted branch. It seems that there is an extra
"\n" at the end of the commit message that it does not expect.
Since backwards compatability needs to be maintained, cannot just make
findAdjustingCommit accept it with the "\n". Will have to instead
have one commitTree variant that uses the old method, and use it for
adjusted branch committing.
This commit is contained in:
parent
2b0df3a76d
commit
a8dd85ea5a
15 changed files with 41 additions and 57 deletions
|
@ -469,7 +469,7 @@ commitAdjustedTree' treesha (BasisBranch basis) parents =
|
||||||
(commitCommitterMetaData basiscommit)
|
(commitCommitterMetaData basiscommit)
|
||||||
(mkcommit cmode)
|
(mkcommit cmode)
|
||||||
mkcommit cmode = Git.Branch.commitTree cmode
|
mkcommit cmode = Git.Branch.commitTree cmode
|
||||||
[adjustedBranchCommitMessage] parents treesha
|
adjustedBranchCommitMessage parents treesha
|
||||||
|
|
||||||
{- This message should never be changed. -}
|
{- This message should never be changed. -}
|
||||||
adjustedBranchCommitMessage :: String
|
adjustedBranchCommitMessage :: String
|
||||||
|
@ -577,7 +577,7 @@ reverseAdjustedCommit commitparent adj (csha, basiscommit) origbranch
|
||||||
(commitAuthorMetaData basiscommit)
|
(commitAuthorMetaData basiscommit)
|
||||||
(commitCommitterMetaData basiscommit) $
|
(commitCommitterMetaData basiscommit) $
|
||||||
Git.Branch.commitTree cmode
|
Git.Branch.commitTree cmode
|
||||||
[commitMessage basiscommit]
|
(commitMessage basiscommit)
|
||||||
[commitparent] treesha
|
[commitparent] treesha
|
||||||
return (Right revadjcommit)
|
return (Right revadjcommit)
|
||||||
|
|
||||||
|
|
|
@ -153,8 +153,7 @@ mergeToAdjustedBranch tomerge (origbranch, adj) mergeconfig canresolvemerge comm
|
||||||
then do
|
then do
|
||||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||||
c <- inRepo $ Git.Branch.commitTree cmode
|
c <- inRepo $ Git.Branch.commitTree cmode
|
||||||
["Merged " ++ fromRef tomerge]
|
("Merged " ++ fromRef tomerge) [adjmergecommit]
|
||||||
[adjmergecommit]
|
|
||||||
(commitTree currentcommit)
|
(commitTree currentcommit)
|
||||||
inRepo $ Git.Branch.update "updating adjusted branch" currbranch c
|
inRepo $ Git.Branch.update "updating adjusted branch" currbranch c
|
||||||
propigateAdjustedCommits origbranch adj
|
propigateAdjustedCommits origbranch adj
|
||||||
|
|
|
@ -945,9 +945,9 @@ rememberTreeishLocked treeish graftpoint jl = do
|
||||||
addedt <- inRepo $ Git.Tree.graftTree treeish graftpoint origtree
|
addedt <- inRepo $ Git.Tree.graftTree treeish graftpoint origtree
|
||||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||||
c <- inRepo $ Git.Branch.commitTree cmode
|
c <- inRepo $ Git.Branch.commitTree cmode
|
||||||
["graft"] [branchref] addedt
|
"graft" [branchref] addedt
|
||||||
c' <- inRepo $ Git.Branch.commitTree cmode
|
c' <- inRepo $ Git.Branch.commitTree cmode
|
||||||
["graft cleanup"] [c] origtree
|
"graft cleanup" [c] origtree
|
||||||
inRepo $ Git.Branch.update' fullname c'
|
inRepo $ Git.Branch.update' fullname c'
|
||||||
-- The tree in c' is the same as the tree in branchref,
|
-- 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
|
-- and the index was updated to that above, so it's safe to
|
||||||
|
|
|
@ -86,7 +86,7 @@ data ImportCommitConfig = ImportCommitConfig
|
||||||
{ importCommitTracking :: Maybe Sha
|
{ importCommitTracking :: Maybe Sha
|
||||||
-- ^ Current commit on the remote tracking branch.
|
-- ^ Current commit on the remote tracking branch.
|
||||||
, importCommitMode :: Git.Branch.CommitMode
|
, importCommitMode :: Git.Branch.CommitMode
|
||||||
, importCommitMessages :: [String]
|
, importCommitMessage :: String
|
||||||
}
|
}
|
||||||
|
|
||||||
{- Buils a commit for an import from a special remote.
|
{- 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
|
mkcommit parents tree = inRepo $ Git.Branch.commitTree
|
||||||
(importCommitMode importcommitconfig)
|
(importCommitMode importcommitconfig)
|
||||||
(importCommitMessages importcommitconfig)
|
(importCommitMessage importcommitconfig)
|
||||||
parents
|
parents
|
||||||
tree
|
tree
|
||||||
|
|
||||||
|
|
|
@ -77,7 +77,7 @@ makeRemoteTrackingBranchMergeCommit' commitsha importedhistory treesha = do
|
||||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||||
inRepo $ Git.Branch.commitTree
|
inRepo $ Git.Branch.commitTree
|
||||||
cmode
|
cmode
|
||||||
["remote tracking branch"]
|
"remote tracking branch"
|
||||||
[commitsha, importedhistory]
|
[commitsha, importedhistory]
|
||||||
treesha
|
treesha
|
||||||
|
|
||||||
|
|
|
@ -577,7 +577,7 @@ updateView view madj = do
|
||||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||||
let msg = "updated " ++ fromRef (branchView view madj)
|
let msg = "updated " ++ fromRef (branchView view madj)
|
||||||
let parent = catMaybes [oldcommit]
|
let parent = catMaybes [oldcommit]
|
||||||
inRepo (Git.Branch.commitTree cmode [msg] parent newtree)
|
inRepo (Git.Branch.commitTree cmode msg parent newtree)
|
||||||
else return Nothing
|
else return Nothing
|
||||||
|
|
||||||
{- Diff between currently checked out branch and staged changes, and
|
{- Diff between currently checked out branch and staged changes, and
|
||||||
|
|
|
@ -13,8 +13,6 @@ git-annex (10.20240228) UNRELEASED; urgency=medium
|
||||||
the same repository.
|
the same repository.
|
||||||
* Windows: Fix escaping output to terminal when using old
|
* Windows: Fix escaping output to terminal when using old
|
||||||
versions of MinTTY.
|
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
|
-- 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
|
liftIO $ removeWhenExistsWith removeLink tmpindex
|
||||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||||
cmessage <- Annex.Branch.commitMessage
|
cmessage <- Annex.Branch.commitMessage
|
||||||
c <- inRepo $ Git.commitTree cmode [cmessage] [] t
|
c <- inRepo $ Git.commitTree cmode cmessage [] t
|
||||||
liftIO $ putStrLn (fromRef c)
|
liftIO $ putStrLn (fromRef c)
|
||||||
where
|
where
|
||||||
ww = WarnUnmatchLsFiles "filter-branch"
|
ww = WarnUnmatchLsFiles "filter-branch"
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git-annex command
|
{- git-annex command
|
||||||
-
|
-
|
||||||
- Copyright 2012-2024 Joey Hess <id@joeyh.name>
|
- Copyright 2012-2021 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -70,7 +70,7 @@ data ImportOptions
|
||||||
, importToSubDir :: Maybe FilePath
|
, importToSubDir :: Maybe FilePath
|
||||||
, importContent :: Bool
|
, importContent :: Bool
|
||||||
, checkGitIgnoreOption :: CheckGitIgnore
|
, checkGitIgnoreOption :: CheckGitIgnore
|
||||||
, messageOption :: [String]
|
, messageOption :: Maybe String
|
||||||
}
|
}
|
||||||
|
|
||||||
optParser :: CmdParamsDesc -> Parser ImportOptions
|
optParser :: CmdParamsDesc -> Parser ImportOptions
|
||||||
|
@ -82,7 +82,7 @@ optParser desc = do
|
||||||
)
|
)
|
||||||
dupmode <- fromMaybe Default <$> optional duplicateModeParser
|
dupmode <- fromMaybe Default <$> optional duplicateModeParser
|
||||||
ic <- Command.Add.checkGitIgnoreSwitch
|
ic <- Command.Add.checkGitIgnoreSwitch
|
||||||
message <- many (strOption
|
message <- optional (strOption
|
||||||
( long "message" <> short 'm' <> metavar "MSG"
|
( long "message" <> short 'm' <> metavar "MSG"
|
||||||
<> help "commit message"
|
<> help "commit message"
|
||||||
))
|
))
|
||||||
|
@ -322,8 +322,8 @@ verifyExisting key destfile (yes, no) = do
|
||||||
verifyEnoughCopiesToDrop [] key Nothing needcopies mincopies [] preverified tocheck
|
verifyEnoughCopiesToDrop [] key Nothing needcopies mincopies [] preverified tocheck
|
||||||
(const yes) no
|
(const yes) no
|
||||||
|
|
||||||
seekRemote :: Remote -> Branch -> Maybe TopFilePath -> Bool -> CheckGitIgnore -> [String] -> CommandSeek
|
seekRemote :: Remote -> Branch -> Maybe TopFilePath -> Bool -> CheckGitIgnore -> Maybe String -> CommandSeek
|
||||||
seekRemote remote branch msubdir importcontent ci importmessages = do
|
seekRemote remote branch msubdir importcontent ci mimportmessage = do
|
||||||
importtreeconfig <- case msubdir of
|
importtreeconfig <- case msubdir of
|
||||||
Nothing -> return ImportTree
|
Nothing -> return ImportTree
|
||||||
Just subdir ->
|
Just subdir ->
|
||||||
|
@ -336,7 +336,7 @@ seekRemote remote branch msubdir importcontent ci importmessages = do
|
||||||
|
|
||||||
trackingcommit <- fromtrackingbranch Git.Ref.sha
|
trackingcommit <- fromtrackingbranch Git.Ref.sha
|
||||||
cmode <- annexCommitMode <$> Annex.getGitConfig
|
cmode <- annexCommitMode <$> Annex.getGitConfig
|
||||||
let importcommitconfig = ImportCommitConfig trackingcommit cmode importmessages'
|
let importcommitconfig = ImportCommitConfig trackingcommit cmode importmessage
|
||||||
let commitimport = commitRemote remote branch tb trackingcommit importtreeconfig importcommitconfig
|
let commitimport = commitRemote remote branch tb trackingcommit importtreeconfig importcommitconfig
|
||||||
|
|
||||||
importabletvar <- liftIO $ newTVarIO Nothing
|
importabletvar <- liftIO $ newTVarIO Nothing
|
||||||
|
@ -353,9 +353,9 @@ seekRemote remote branch msubdir importcontent ci importmessages = do
|
||||||
includeCommandAction $
|
includeCommandAction $
|
||||||
commitimport imported
|
commitimport imported
|
||||||
where
|
where
|
||||||
importmessages'
|
importmessage = fromMaybe
|
||||||
| null importmessages = ["import from " ++ Remote.name remote]
|
("import from " ++ Remote.name remote)
|
||||||
| otherwise = importmessages
|
mimportmessage
|
||||||
|
|
||||||
tb = mkRemoteTrackingBranch remote branch
|
tb = mkRemoteTrackingBranch remote branch
|
||||||
|
|
||||||
|
|
|
@ -1,7 +1,7 @@
|
||||||
{- git-annex command
|
{- git-annex command
|
||||||
-
|
-
|
||||||
- Copyright 2011 Joachim Breitner <mail@joachim-breitner.de>
|
- Copyright 2011 Joachim Breitner <mail@joachim-breitner.de>
|
||||||
- Copyright 2011-2024 Joey Hess <id@joeyh.name>
|
- Copyright 2011-2023 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -105,7 +105,7 @@ data SyncOptions = SyncOptions
|
||||||
, notOnlyAnnexOption :: Bool
|
, notOnlyAnnexOption :: Bool
|
||||||
, commitOption :: Bool
|
, commitOption :: Bool
|
||||||
, noCommitOption :: Bool
|
, noCommitOption :: Bool
|
||||||
, messageOption :: [String]
|
, messageOption :: Maybe String
|
||||||
, pullOption :: Bool
|
, pullOption :: Bool
|
||||||
, pushOption :: Bool
|
, pushOption :: Bool
|
||||||
, contentOption :: Maybe Bool
|
, contentOption :: Maybe Bool
|
||||||
|
@ -125,7 +125,7 @@ instance Default SyncOptions where
|
||||||
, notOnlyAnnexOption = False
|
, notOnlyAnnexOption = False
|
||||||
, commitOption = False
|
, commitOption = False
|
||||||
, noCommitOption = False
|
, noCommitOption = False
|
||||||
, messageOption = []
|
, messageOption = Nothing
|
||||||
, pullOption = False
|
, pullOption = False
|
||||||
, pushOption = False
|
, pushOption = False
|
||||||
, contentOption = Just False
|
, contentOption = Just False
|
||||||
|
@ -169,8 +169,8 @@ optParser mode desc = SyncOptions
|
||||||
( long "no-commit"
|
( long "no-commit"
|
||||||
<> help "avoid git commit"
|
<> help "avoid git commit"
|
||||||
))
|
))
|
||||||
<*> unlessmode [SyncMode, AssistMode] []
|
<*> unlessmode [SyncMode, AssistMode] Nothing
|
||||||
(many (strOption
|
(optional (strOption
|
||||||
( long "message" <> short 'm' <> metavar "MSG"
|
( long "message" <> short 'm' <> metavar "MSG"
|
||||||
<> help "commit message"
|
<> help "commit message"
|
||||||
)))
|
)))
|
||||||
|
@ -402,18 +402,17 @@ syncRemotes' ps available =
|
||||||
|
|
||||||
commit :: SyncOptions -> CommandStart
|
commit :: SyncOptions -> CommandStart
|
||||||
commit o = stopUnless shouldcommit $ starting "commit" ai si $ do
|
commit o = stopUnless shouldcommit $ starting "commit" ai si $ do
|
||||||
|
commitmessage <- maybe commitMsg return (messageOption o)
|
||||||
Annex.Branch.commit =<< Annex.Branch.commitMessage
|
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
|
next $ do
|
||||||
showOutput
|
showOutput
|
||||||
let cmode = Git.Branch.ManualCommit
|
let cmode = Git.Branch.ManualCommit
|
||||||
cquiet <- Git.Branch.CommitQuiet <$> commandProgressDisabled
|
cquiet <- Git.Branch.CommitQuiet <$> commandProgressDisabled
|
||||||
void $ inRepo $ Git.Branch.commitCommand
|
void $ inRepo $ Git.Branch.commitCommand cmode cquiet
|
||||||
cmode cquiet
|
[ Param "-a"
|
||||||
([ Param "-a" ] ++ mopts)
|
, Param "-m"
|
||||||
|
, Param commitmessage
|
||||||
|
]
|
||||||
return True
|
return True
|
||||||
where
|
where
|
||||||
shouldcommit = notOnlyAnnex o <&&>
|
shouldcommit = notOnlyAnnex o <&&>
|
||||||
|
@ -427,8 +426,7 @@ commitMsg :: Annex String
|
||||||
commitMsg = do
|
commitMsg = do
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
m <- uuidDescMap
|
m <- uuidDescMap
|
||||||
return $ "git-annex in "
|
return $ "git-annex in " ++ maybe "unknown" fromUUIDDesc (M.lookup u m)
|
||||||
++ maybe "unknown" fromUUIDDesc (M.lookup u m)
|
|
||||||
|
|
||||||
mergeLocal :: [Git.Merge.MergeConfig] -> SyncOptions -> CurrBranch -> CommandStart
|
mergeLocal :: [Git.Merge.MergeConfig] -> SyncOptions -> CurrBranch -> CommandStart
|
||||||
mergeLocal mergeconfig o currbranch = stopUnless (notOnlyAnnex o) $
|
mergeLocal mergeconfig o currbranch = stopUnless (notOnlyAnnex o) $
|
||||||
|
@ -580,7 +578,7 @@ importRemote importcontent o remote currbranch
|
||||||
let (branch, subdir) = splitRemoteAnnexTrackingBranchSubdir b
|
let (branch, subdir) = splitRemoteAnnexTrackingBranchSubdir b
|
||||||
if canImportKeys remote importcontent
|
if canImportKeys remote importcontent
|
||||||
then do
|
then do
|
||||||
Command.Import.seekRemote remote branch subdir importcontent (CheckGitIgnore True) []
|
Command.Import.seekRemote remote branch subdir importcontent (CheckGitIgnore True) Nothing
|
||||||
-- Importing generates a branch
|
-- Importing generates a branch
|
||||||
-- that is not initially connected
|
-- that is not initially connected
|
||||||
-- to the current branch, so allow
|
-- to the current branch, so allow
|
||||||
|
|
|
@ -178,7 +178,7 @@ commit commitmode allowempty message branch parentrefs repo = do
|
||||||
tree <- writeTree repo
|
tree <- writeTree repo
|
||||||
ifM (cancommit tree)
|
ifM (cancommit tree)
|
||||||
( do
|
( do
|
||||||
sha <- commitTree commitmode [message] parentrefs tree repo
|
sha <- commitTree commitmode message parentrefs tree repo
|
||||||
update' branch sha repo
|
update' branch sha repo
|
||||||
return $ Just sha
|
return $ Just sha
|
||||||
, return Nothing
|
, return Nothing
|
||||||
|
@ -207,15 +207,15 @@ writeTreeQuiet repo = extractSha <$> withNullHandle go
|
||||||
go nullh = pipeReadStrict' (\p -> p { std_err = UseHandle nullh })
|
go nullh = pipeReadStrict' (\p -> p { std_err = UseHandle nullh })
|
||||||
[Param "write-tree"] repo
|
[Param "write-tree"] repo
|
||||||
|
|
||||||
commitTree :: CommitMode -> [String] -> [Ref] -> Ref -> Repo -> IO Sha
|
commitTree :: CommitMode -> String -> [Ref] -> Ref -> Repo -> IO Sha
|
||||||
commitTree commitmode messages parentrefs tree repo =
|
commitTree commitmode message parentrefs tree repo =
|
||||||
getSha "commit-tree" $ pipeReadStrict ps repo
|
getSha "commit-tree" $
|
||||||
|
pipeWriteRead ([Param "commit-tree", Param (fromRef tree)] ++ ps)
|
||||||
|
sendmsg repo
|
||||||
where
|
where
|
||||||
ps = [Param "commit-tree", Param (fromRef tree)]
|
sendmsg = Just $ flip hPutStr message
|
||||||
++ applyCommitModeForCommitTree commitmode baseparams repo
|
ps = applyCommitModeForCommitTree commitmode parentparams repo
|
||||||
baseparams = map Param $
|
parentparams = map Param $ concatMap (\r -> ["-p", fromRef r]) parentrefs
|
||||||
concatMap (\r -> ["-p", fromRef r]) parentrefs
|
|
||||||
++ concatMap (\msg -> ["-m", msg]) messages
|
|
||||||
|
|
||||||
{- A leading + makes git-push force pushing a branch. -}
|
{- A leading + makes git-push force pushing a branch. -}
|
||||||
forcePush :: String -> String
|
forcePush :: String -> String
|
||||||
|
|
|
@ -34,9 +34,6 @@ files that it does not match will instead be added with `git add`.
|
||||||
|
|
||||||
Use this option to specify a commit message.
|
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`
|
* `--content-of=path` `-C path`
|
||||||
|
|
||||||
Only add, pull, and push files in the given path.
|
Only add, pull, and push files in the given path.
|
||||||
|
|
|
@ -107,9 +107,6 @@ 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
|
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.
|
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
|
# IMPORTING FROM A DIRECTORY
|
||||||
|
|
||||||
When run with a path, `git annex import` **moves** files from somewhere outside
|
When run with a path, `git annex import` **moves** files from somewhere outside
|
||||||
|
|
|
@ -51,9 +51,6 @@ when syncing with repositories that have preferred content configured.
|
||||||
|
|
||||||
Use this option to specify a commit message.
|
Use this option to specify a commit message.
|
||||||
|
|
||||||
If multiple -m options are given, their values are concatenated
|
|
||||||
as separate paragraphs.
|
|
||||||
|
|
||||||
* `--pull`, `--no-pull`
|
* `--pull`, `--no-pull`
|
||||||
|
|
||||||
Use this option to disable pulling.
|
Use this option to disable pulling.
|
||||||
|
|
|
@ -1,4 +1,2 @@
|
||||||
git-annex sync etc -m should be able to be specified multiple times. In git
|
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]]
|
commit, multiple -m can be used to make a multiparagraph commit. --[[Joey]]
|
||||||
|
|
||||||
> [[done]]
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue