diffdriver: New git-annex command, to make git external diff drivers work with annexed files.

Closes https://github.com/datalad/datalad/issues/18
This commit is contained in:
Joey Hess 2014-11-24 16:14:01 -04:00
parent 6db880be11
commit 6ecd3ff421
6 changed files with 133 additions and 4 deletions

View file

@ -35,13 +35,17 @@ isAnnexLink file = maybe Nothing (fileKey . takeFileName) <$> getAnnexLinkTarget
- content.
-}
getAnnexLinkTarget :: FilePath -> Annex (Maybe LinkTarget)
getAnnexLinkTarget file = ifM (coreSymlinks <$> Annex.getGitConfig)
( check readSymbolicLink $
getAnnexLinkTarget f = getAnnexLinkTarget' f
=<< (coreSymlinks <$> Annex.getGitConfig)
{- Pass False to force looking inside file. -}
getAnnexLinkTarget' :: FilePath -> Bool -> Annex (Maybe LinkTarget)
getAnnexLinkTarget' file coresymlinks = if coresymlinks
then check readSymbolicLink $
return Nothing
, check readSymbolicLink $
else check readSymbolicLink $
check probefilecontent $
return Nothing
)
where
check getlinktarget fallback = do
v <- liftIO $ catchMaybeIO $ getlinktarget file

View file

@ -84,6 +84,7 @@ import qualified Command.Indirect
import qualified Command.Upgrade
import qualified Command.Forget
import qualified Command.Proxy
import qualified Command.DiffDriver
import qualified Command.Undo
import qualified Command.Version
import qualified Command.Help
@ -178,6 +179,7 @@ cmds = concat
, Command.Upgrade.cmd
, Command.Forget.cmd
, Command.Proxy.cmd
, Command.DiffDriver.cmd
, Command.Undo.cmd
, Command.Version.cmd
, Command.Help.cmd

102
Command/DiffDriver.hs Normal file
View file

@ -0,0 +1,102 @@
{- git-annex command
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.DiffDriver where
import Common.Annex
import Command
import Annex.Content
import Annex.Link
import Git.Types
cmd :: [Command]
cmd = [dontCheck repoExists $
command "diffdriver" ("[-- cmd --opts]") seek
SectionPlumbing "external git diff driver shim"]
seek :: CommandSeek
seek = withWords start
start :: [String] -> CommandStart
start opts = do
let (req, differ) = parseReq opts
void $ liftIO . exitBool =<< liftIO . differ =<< fixupReq req
stop
data Req
= Req
{ rPath :: FilePath
, rOldFile :: FilePath
, rOldHex :: String
, rOldMode :: String
, rNewFile :: FilePath
, rNewHex :: String
, rNewMode ::String
}
| UnmergedReq
{ rPath :: FilePath
}
type Differ = Req -> IO Bool
serializeReq :: Req -> [CommandParam]
serializeReq req@(UnmergedReq {}) = [Param $ rPath req]
serializeReq req@(Req {}) = map Param
[ rPath req
, rOldFile req
, rOldHex req
, rOldMode req
, rNewFile req
, rNewHex req
, rNewMode req
]
parseReq :: [String] -> (Req, Differ)
parseReq opts = case separate (== "--") opts of
(c:ps, l) -> (mk l, externalDiffer c ps)
([],_) -> badopts
where
mk (path:old_file:old_hex:old_mode:new_file:new_hex:new_mode:[]) =
Req
{ rPath = path
, rOldFile = old_file
, rOldHex = old_hex
, rOldMode = old_mode
, rNewFile = new_file
, rNewHex = new_hex
, rNewMode = new_mode
}
mk (unmergedpath:[]) = UnmergedReq { rPath = unmergedpath }
mk _ = badopts
badopts = error $ "Unexpected input: " ++ unwords opts
{- Check if either file is a symlink to a git-annex object,
- which git-diff will leave as a normal file containing the link text.
- Adjust the Req to instead point to the actual location of the annexed
- object (which may or may not exist). -}
fixupReq :: Req -> Annex Req
fixupReq req@(UnmergedReq {}) = return req
fixupReq req@(Req {}) =
check rOldFile rOldMode (\r f -> r { rOldFile = f }) req
>>= check rNewFile rNewMode (\r f -> r { rNewFile = f })
where
check getfile getmode setfile r = case readBlobType (getmode r) of
Just SymlinkBlob -> do
v <- getAnnexLinkTarget' (getfile r) False
case fileKey . takeFileName =<< v of
Nothing -> return r
Just k -> setfile r <$>
withObjectLoc k
-- indirect mode
return
-- direct mode
(return . Prelude.head)
_ -> return r
externalDiffer :: String -> [String] -> Differ
externalDiffer c ps = \req -> boolSystem c (map Param ps ++ serializeReq req )

2
debian/changelog vendored
View file

@ -13,6 +13,8 @@ git-annex (5.20141126) UNRELEASED; urgency=medium
* Debian package is now maintained by Gergely Nagy.
* Windows: Remove Alt+A keyboard shortcut, which turns out to have scope
outside the menus.
* diffdriver: New git-annex command, to make git external diff drivers
work with annexed files.
-- Joey Hess <joeyh@debian.org> Mon, 10 Nov 2014 15:31:55 -0400

View file

@ -989,6 +989,21 @@ subdirectories).
Merge conflicts between two files that are not annexed will not be
automatically resolved.
* `diffdriver`
This is an external git diff driver shim. Normally, when using `git diff`
with an external git driver, the symlinks to annexed files are not set up
right, so the external git driver cannot read them in order to perform
smart diffing of their contents. This command works around the problem,
by passing the fixed up files to the real external diff driver.
To use, just configure git to use "git-annex diffdriver -- cmd params --"
as the external diff command, where cmd is the real external diff
command you want to use, and params are any extra parameters to pass
to it. Note the trailing "--", which is required.
For example, set `GIT_EXTERNAL_DIFF=git-annex diffdriver -- j-c-diff --`
* `remotedaemon`
Detects when network remotes have received git pushes and fetches from them.

View file

@ -7,3 +7,7 @@ Should be relatively simple, only there would have to be a way to deal with the
Of course you wouldn't want to diff two large files, but with git annex assistant, all files are annexed by default (right?), so this would be useful.
There might already be a way to easily diff two versions of an annexed file which I'm missing -- in that case please point me to it! :)
> [[done]]; rather than adding a `git annex diff`, I made git-annex be able to be used as a git diff driver command,
> which in turn can run some third-party external diff driver that does
> some smart handling of binary files.