Removed support for git versions older than 2.1

debian oldoldstable has 2.1, and that's what i386ancient uses. It would be
better to require git 2.2, which is needed to use adjusted branches, but
can't do that w/o losing support for some old linux kernels or a
complicated git backport.
This commit is contained in:
Joey Hess 2019-09-11 16:10:25 -04:00
parent 99b509572d
commit fef3cd055d
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
12 changed files with 42 additions and 86 deletions

View file

@ -118,7 +118,7 @@ data AnnexState = AnnexState
, catfilehandles :: M.Map FilePath CatFileHandle , catfilehandles :: M.Map FilePath CatFileHandle
, hashobjecthandle :: Maybe HashObjectHandle , hashobjecthandle :: Maybe HashObjectHandle
, checkattrhandle :: Maybe CheckAttrHandle , checkattrhandle :: Maybe CheckAttrHandle
, checkignorehandle :: Maybe (Maybe CheckIgnoreHandle) , checkignorehandle :: Maybe CheckIgnoreHandle
, forcebackend :: Maybe String , forcebackend :: Maybe String
, globalnumcopies :: Maybe NumCopies , globalnumcopies :: Maybe NumCopies
, forcenumcopies :: Maybe NumCopies , forcenumcopies :: Maybe NumCopies

View file

@ -19,23 +19,19 @@ import qualified Annex
checkIgnored :: FilePath -> Annex Bool checkIgnored :: FilePath -> Annex Bool
checkIgnored file = go =<< checkIgnoreHandle checkIgnored file = go =<< checkIgnoreHandle
where where
go Nothing = return False go h = liftIO $ Git.checkIgnored h file
go (Just h) = liftIO $ Git.checkIgnored h file
checkIgnoreHandle :: Annex (Maybe Git.CheckIgnoreHandle) checkIgnoreHandle :: Annex Git.CheckIgnoreHandle
checkIgnoreHandle = maybe startup return =<< Annex.getState Annex.checkignorehandle checkIgnoreHandle = maybe startup return =<< Annex.getState Annex.checkignorehandle
where where
startup = do startup = do
v <- inRepo Git.checkIgnoreStart h <- inRepo Git.checkIgnoreStart
when (isNothing v) $ Annex.changeState $ \s -> s { Annex.checkignorehandle = Just h }
warning "The installed version of git is too old for .gitignores to be honored by git-annex." return h
Annex.changeState $ \s -> s { Annex.checkignorehandle = Just v }
return v
checkIgnoreStop :: Annex () checkIgnoreStop :: Annex ()
checkIgnoreStop = maybe noop stop =<< Annex.getState Annex.checkignorehandle checkIgnoreStop = maybe noop stop =<< Annex.getState Annex.checkignorehandle
where where
stop (Just h) = do stop h = do
liftIO $ Git.checkIgnoreStop h liftIO $ Git.checkIgnoreStop h
Annex.changeState $ \s -> s { Annex.checkignorehandle = Nothing } Annex.changeState $ \s -> s { Annex.checkignorehandle = Nothing }
stop Nothing = noop

View file

@ -12,7 +12,6 @@ import Git.Config
import Types.GitConfig import Types.GitConfig
import Config.Files import Config.Files
import qualified Git import qualified Git
import qualified Git.BuildVersion
import Utility.Path import Utility.Path
import Utility.SafeCommand import Utility.SafeCommand
import Utility.Directory import Utility.Directory
@ -42,10 +41,8 @@ fixupRepo r c = do
{- Disable git's built-in wildcard expansion, which is not wanted {- Disable git's built-in wildcard expansion, which is not wanted
- when using it as plumbing by git-annex. -} - when using it as plumbing by git-annex. -}
disableWildcardExpansion :: Repo -> Repo disableWildcardExpansion :: Repo -> Repo
disableWildcardExpansion r disableWildcardExpansion r = r
| Git.BuildVersion.older "1.8.1" = r { gitGlobalOpts = gitGlobalOpts r ++ [Param "--literal-pathspecs"] }
| otherwise = r
{ gitGlobalOpts = gitGlobalOpts r ++ [Param "--literal-pathspecs"] }
{- Direct mode repos have core.bare=true, but are not really bare. {- Direct mode repos have core.bare=true, but are not really bare.
- Fix up the Repo to be a non-bare repo, and arrange for git commands - Fix up the Repo to be a non-bare repo, and arrange for git commands

View file

@ -62,7 +62,7 @@ getGitVersion = go =<< getEnv "FORCE_GIT_VERSION"
go (Just s) = return $ Config "gitversion" $ StringConfig s go (Just s) = return $ Config "gitversion" $ StringConfig s
go Nothing = do go Nothing = do
v <- Git.Version.installed v <- Git.Version.installed
let oldestallowed = Git.Version.normalize "1.7.1.0" let oldestallowed = Git.Version.normalize "2.1"
when (v < oldestallowed) $ when (v < oldestallowed) $
error $ "installed git version " ++ show v ++ " is too old! (Need " ++ show oldestallowed ++ " or newer)" error $ "installed git version " ++ show v ++ " is too old! (Need " ++ show oldestallowed ++ " or newer)"
return $ Config "gitversion" $ StringConfig $ show v return $ Config "gitversion" $ StringConfig $ show v

View file

@ -31,6 +31,7 @@ git-annex (7.20190826) UNRELEASED; urgency=medium
* init: Catch more exceptions when testing locking. * init: Catch more exceptions when testing locking.
* init: Fix a reversion that broke initialization on systems that * init: Fix a reversion that broke initialization on systems that
need to use pid locking. need to use pid locking.
* Removed support for git versions older than 2.1.
-- Joey Hess <id@joeyh.name> Sat, 24 Aug 2019 12:54:35 -0400 -- Joey Hess <id@joeyh.name> Sat, 24 Aug 2019 12:54:35 -0400

View file

@ -15,7 +15,6 @@ import Git.Sha
import Git.Command import Git.Command
import qualified Git.Config import qualified Git.Config
import qualified Git.Ref import qualified Git.Ref
import qualified Git.BuildVersion
{- The currently checked out branch. {- The currently checked out branch.
- -
@ -125,8 +124,7 @@ data CommitMode = ManualCommit | AutomaticCommit
{- Prevent signing automatic commits. -} {- Prevent signing automatic commits. -}
applyCommitMode :: CommitMode -> [CommandParam] -> [CommandParam] applyCommitMode :: CommitMode -> [CommandParam] -> [CommandParam]
applyCommitMode commitmode ps applyCommitMode commitmode ps
| commitmode == AutomaticCommit && not (Git.BuildVersion.older "2.0.0") = | commitmode == AutomaticCommit = Param "--no-gpg-sign" : ps
Param "--no-gpg-sign" : ps
| otherwise = ps | otherwise = ps
{- Some versions of git commit-tree honor commit.gpgsign themselves, {- Some versions of git commit-tree honor commit.gpgsign themselves,

View file

@ -10,12 +10,11 @@ module Git.CheckAttr where
import Common import Common
import Git import Git
import Git.Command import Git.Command
import qualified Git.Version
import qualified Utility.CoProcess as CoProcess import qualified Utility.CoProcess as CoProcess
import System.IO.Error import System.IO.Error
type CheckAttrHandle = (CoProcess.CoProcessHandle, [Attr], Bool, String) type CheckAttrHandle = (CoProcess.CoProcessHandle, [Attr], String)
type Attr = String type Attr = String
@ -25,8 +24,7 @@ checkAttrStart :: [Attr] -> Repo -> IO CheckAttrHandle
checkAttrStart attrs repo = do checkAttrStart attrs repo = do
currdir <- getCurrentDirectory currdir <- getCurrentDirectory
h <- gitCoProcessStart True params repo h <- gitCoProcessStart True params repo
oldgit <- Git.Version.older "1.7.7" return (h, attrs, currdir)
return (h, attrs, oldgit, currdir)
where where
params = params =
[ Param "check-attr" [ Param "check-attr"
@ -36,12 +34,12 @@ checkAttrStart attrs repo = do
[ Param "--" ] [ Param "--" ]
checkAttrStop :: CheckAttrHandle -> IO () checkAttrStop :: CheckAttrHandle -> IO ()
checkAttrStop (h, _, _, _) = CoProcess.stop h checkAttrStop (h, _, _) = CoProcess.stop h
{- Gets an attribute of a file. When the attribute is not specified, {- Gets an attribute of a file. When the attribute is not specified,
- returns "" -} - returns "" -}
checkAttr :: CheckAttrHandle -> Attr -> FilePath -> IO String checkAttr :: CheckAttrHandle -> Attr -> FilePath -> IO String
checkAttr (h, attrs, oldgit, currdir) want file = do checkAttr (h, attrs, currdir) want file = do
pairs <- CoProcess.query h send (receive "") pairs <- CoProcess.query h send (receive "")
let vals = map snd $ filter (\(attr, _) -> attr == want) pairs let vals = map snd $ filter (\(attr, _) -> attr == want) pairs
case vals of case vals of
@ -78,16 +76,9 @@ checkAttr (h, attrs, oldgit, currdir) want file = do
else Nothing -- line incomplete else Nothing -- line incomplete
numattrs = length attrs numattrs = length attrs
{- Before git 1.7.7, git check-attr worked best with {- git check-attr chokes on some absolute filenames,
- absolute filenames; using them worked around some bugs - so make sure the filename is relative. -}
- with relative filenames. file' = relPathDirToFileAbs currdir $ absPathFrom currdir file
-
- With newer git, git check-attr chokes on some absolute
- filenames, and the bugs that necessitated them were fixed,
- so use relative filenames. -}
file'
| oldgit = absPathFrom currdir file
| otherwise = relPathDirToFileAbs currdir $ absPathFrom currdir file
oldattrvalue attr l = end bits !! 0 oldattrvalue attr l = end bits !! 0
where where
bits = split sep l bits = split sep l

View file

@ -15,7 +15,6 @@ module Git.CheckIgnore (
import Common import Common
import Git import Git
import Git.Command import Git.Command
import qualified Git.Version
import qualified Utility.CoProcess as CoProcess import qualified Utility.CoProcess as CoProcess
import System.IO.Error import System.IO.Error
@ -29,17 +28,11 @@ type CheckIgnoreHandle = CoProcess.CoProcessHandle
- GIT_FLUSH behavior flushing the output buffer when git check-ignore - GIT_FLUSH behavior flushing the output buffer when git check-ignore
- is piping to us. - is piping to us.
- -
- The first version of git to support what we need is 1.8.4.
- Nothing is returned if an older git is installed.
-
- check-ignore does not support --literal-pathspecs, so remove that - check-ignore does not support --literal-pathspecs, so remove that
- from the gitGlobalOpts if set. - from the gitGlobalOpts if set.
-} -}
checkIgnoreStart :: Repo -> IO (Maybe CheckIgnoreHandle) checkIgnoreStart :: Repo -> IO CheckIgnoreHandle
checkIgnoreStart repo = ifM supportedGitVersion checkIgnoreStart repo = gitCoProcessStart True params repo'
( Just <$> gitCoProcessStart True params repo'
, return Nothing
)
where where
params = params =
[ Param "check-ignore" [ Param "check-ignore"
@ -52,11 +45,6 @@ checkIgnoreStart repo = ifM supportedGitVersion
pathspecs (Param "--literal-pathspecs") = True pathspecs (Param "--literal-pathspecs") = True
pathspecs _ = False pathspecs _ = False
supportedGitVersion :: IO Bool
supportedGitVersion = do
v <- Git.Version.installed
return $ v >= Git.Version.normalize "1.8.4"
{- For some reason, check-ignore --batch always exits nonzero, {- For some reason, check-ignore --batch always exits nonzero,
- so ignore any error. -} - so ignore any error. -}
checkIgnoreStop :: CheckIgnoreHandle -> IO () checkIgnoreStop :: CheckIgnoreHandle -> IO ()

View file

@ -22,7 +22,6 @@ import Git
import Git.Command import Git.Command
import Git.Sha import Git.Sha
import Utility.Batch import Utility.Batch
import qualified Git.Version
import qualified Data.Set as S import qualified Data.Set as S
import Control.Concurrent.Async import Control.Concurrent.Async
@ -73,9 +72,7 @@ instance Monoid FsckOutput where
-} -}
findBroken :: Bool -> Repo -> IO FsckResults findBroken :: Bool -> Repo -> IO FsckResults
findBroken batchmode r = do findBroken batchmode r = do
supportsNoDangling <- (>= Git.Version.normalize "1.7.10") let (command, params) = ("git", fsckParams r)
<$> Git.Version.installed
let (command, params) = ("git", fsckParams supportsNoDangling r)
(command', params') <- if batchmode (command', params') <- if batchmode
then toBatchCommand (command, params) then toBatchCommand (command, params)
else return (command, params) else return (command, params)
@ -86,8 +83,8 @@ findBroken batchmode r = do
, std_err = CreatePipe , std_err = CreatePipe
} }
(o1, o2) <- concurrently (o1, o2) <- concurrently
(parseFsckOutput maxobjs r supportsNoDangling (stdoutHandle p)) (parseFsckOutput maxobjs r (stdoutHandle p))
(parseFsckOutput maxobjs r supportsNoDangling (stderrHandle p)) (parseFsckOutput maxobjs r (stderrHandle p))
fsckok <- checkSuccessProcess pid fsckok <- checkSuccessProcess pid
case mappend o1 o2 of case mappend o1 o2 of
FsckOutput badobjs truncated FsckOutput badobjs truncated
@ -120,15 +117,15 @@ knownMissing (FsckFoundMissing s _) = s
findMissing :: [Sha] -> Repo -> IO MissingObjects findMissing :: [Sha] -> Repo -> IO MissingObjects
findMissing objs r = S.fromList <$> filterM (`isMissing` r) objs findMissing objs r = S.fromList <$> filterM (`isMissing` r) objs
parseFsckOutput :: Int -> Repo -> Bool -> Handle -> IO FsckOutput parseFsckOutput :: Int -> Repo -> Handle -> IO FsckOutput
parseFsckOutput maxobjs r supportsNoDangling h = do parseFsckOutput maxobjs r h = do
ls <- lines <$> hGetContents h ls <- lines <$> hGetContents h
if null ls if null ls
then return NoFsckOutput then return NoFsckOutput
else if all ("duplicateEntries" `isInfixOf`) ls else if all ("duplicateEntries" `isInfixOf`) ls
then return AllDuplicateEntriesWarning then return AllDuplicateEntriesWarning
else do else do
let shas = findShas supportsNoDangling ls let shas = findShas ls
let !truncated = length shas > maxobjs let !truncated = length shas > maxobjs
missingobjs <- findMissing (take maxobjs shas) r missingobjs <- findMissing (take maxobjs shas) r
return $ FsckOutput missingobjs truncated return $ FsckOutput missingobjs truncated
@ -141,18 +138,14 @@ isMissing s r = either (const True) (const False) <$> tryIO dump
, Param (fromRef s) , Param (fromRef s)
] r ] r
findShas :: Bool -> [String] -> [Sha] findShas :: [String] -> [Sha]
findShas supportsNoDangling = catMaybes . map extractSha . concat . map words . filter wanted findShas = catMaybes . map extractSha . concat . map words . filter wanted
where where
wanted l wanted l = not ("dangling " `isPrefixOf` l)
| supportsNoDangling = True
| otherwise = not ("dangling " `isPrefixOf` l)
fsckParams :: Bool -> Repo -> [CommandParam] fsckParams :: Repo -> [CommandParam]
fsckParams supportsNoDangling = gitCommandLine $ map Param $ catMaybes fsckParams = gitCommandLine $ map Param
[ Just "fsck" [ "fsck"
, if supportsNoDangling , "--no-dangling"
then Just "--no-dangling" , "--no-reflogs"
else Nothing
, Just "--no-reflogs"
] ]

View file

@ -17,7 +17,6 @@ module Git.Merge (
import Common import Common
import Git import Git
import Git.Command import Git.Command
import qualified Git.BuildVersion
import qualified Git.Version import qualified Git.Version
import Git.Branch (CommitMode(..)) import Git.Branch (CommitMode(..))
@ -33,7 +32,7 @@ merge = merge' []
merge' :: [CommandParam] -> Ref -> [MergeConfig] -> CommitMode -> Repo -> IO Bool merge' :: [CommandParam] -> Ref -> [MergeConfig] -> CommitMode -> Repo -> IO Bool
merge' extraparams branch mergeconfig commitmode r merge' extraparams branch mergeconfig commitmode r
| MergeNonInteractive `notElem` mergeconfig || Git.BuildVersion.older "1.7.7.6" = | MergeNonInteractive `notElem` mergeconfig =
go [Param $ fromRef branch] go [Param $ fromRef branch]
| otherwise = go [Param "--no-edit", Param $ fromRef branch] | otherwise = go [Param "--no-edit", Param $ fromRef branch]
where where

View file

@ -13,17 +13,10 @@ import Common
import Git import Git
import Git.Types import Git.Types
import qualified Git.Command import qualified Git.Command
import qualified Git.Version
remove :: RemoteName -> Repo -> IO () remove :: RemoteName -> Repo -> IO ()
remove remotename r = do remove remotename = Git.Command.run
old <- Git.Version.older "1.8.0" [ Param "remote"
Git.Command.run , Param "remove"
[ Param "remote" , Param remotename
-- name of this subcommand changed ]
, Param $
if old
then "rm"
else "remove"
, Param remotename
] r

2
debian/control vendored
View file

@ -81,7 +81,7 @@ Build-Depends:
lsof [linux-any], lsof [linux-any],
ikiwiki, ikiwiki,
libimage-magick-perl, libimage-magick-perl,
git (>= 1:1.8.1), git (>= 1:2.1),
rsync, rsync,
curl, curl,
openssh-client, openssh-client,